{-# LANGUAGE BangPatterns, CPP, GADTs, OverloadedStrings, RankNTypes,
RecordWildCards #-}
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
, stringCI
, take
, scan
, runScanner
, takeWhile
, takeWhile1
, takeWhileIncluding
, takeTill
, getChunk
, takeByteString
, takeLazyByteString
, endOfLine
, endOfInput
, match
, atEnd
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Control.Applicative ((<|>))
import Control.Monad (when)
import Data.Attoparsec.ByteString.Buffer (Buffer, buffer)
import Data.Attoparsec.ByteString.FastSet (charClass, memberWord8)
import Data.Attoparsec.Combinator ((<?>))
import Data.Attoparsec.Internal
import Data.Attoparsec.Internal.Compat
import Data.Attoparsec.Internal.Fhthagn (inlinePerformIO)
import Data.Attoparsec.Internal.Types hiding (Parser, Failure, Success)
import Data.ByteString (ByteString)
import Data.List (intercalate)
import Data.Word (Word8)
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (castPtr, minusPtr, plusPtr)
import Foreign.Storable (Storable(peek, sizeOf))
import Prelude hiding (getChar, succ, take, takeWhile)
import qualified Data.Attoparsec.ByteString.Buffer as Buf
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
type Parser = T.Parser ByteString
type Result = IResult ByteString
type Failure r = T.Failure ByteString Buffer r
type Success a r = T.Success ByteString Buffer a r
satisfy :: (Word8 -> Bool) -> Parser Word8
satisfy :: (Word8 -> Bool) -> Parser Word8
satisfy Word8 -> Bool
p = do
Word8
h <- Parser Word8
peekWord8'
if Word8 -> Bool
p Word8
h
then Int -> Parser ()
advance Int
1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Word8
h
else forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"satisfy"
{-# INLINE satisfy #-}
skip :: (Word8 -> Bool) -> Parser ()
skip :: (Word8 -> Bool) -> Parser ()
skip Word8 -> Bool
p = do
Word8
h <- Parser Word8
peekWord8'
if Word8 -> Bool
p Word8
h
then Int -> Parser ()
advance Int
1
else forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"skip"
satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
satisfyWith :: forall a. (Word8 -> a) -> (a -> Bool) -> Parser a
satisfyWith Word8 -> a
f a -> Bool
p = do
Word8
h <- Parser Word8
peekWord8'
let c :: a
c = Word8 -> a
f Word8
h
if a -> Bool
p a
c
then Int -> Parser ()
advance Int
1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return a
c
else forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"satisfyWith"
{-# INLINE satisfyWith #-}
storable :: Storable a => Parser a
storable :: forall a. Storable a => Parser a
storable = forall b. Storable b => b -> Parser b
hack forall a. HasCallStack => a
undefined
where
hack :: Storable b => b -> Parser b
hack :: forall b. Storable b => b -> Parser b
hack b
dummy = do
(ForeignPtr Word8
fp,Int
o,Int
_) <- ByteString -> (ForeignPtr Word8, Int, Int)
B.toForeignPtr forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Int -> Parser ByteString
take (forall a. Storable a => a -> Int
sizeOf b
dummy)
forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IO a -> a
inlinePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Ptr b
castPtr forall a b. (a -> b) -> a -> b
$ Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
o)
take :: Int -> Parser ByteString
take :: Int -> Parser ByteString
take Int
n0 = do
let n :: Int
n = forall a. Ord a => a -> a -> a
max Int
n0 Int
0
ByteString
s <- Int -> Parser ByteString
ensure Int
n
Int -> Parser ()
advance Int
n forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
s
{-# INLINE take #-}
string :: ByteString -> Parser ByteString
string :: ByteString -> Parser ByteString
string ByteString
s = (forall r.
ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r)
-> (ByteString -> ByteString) -> ByteString -> Parser ByteString
string_ (forall r.
(ByteString -> ByteString)
-> ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
stringSuspended forall a. a -> a
id) forall a. a -> a
id ByteString
s
{-# INLINE string #-}
toLower :: Word8 -> Word8
toLower :: Word8 -> Word8
toLower Word8
w | Word8
w forall a. Ord a => a -> a -> Bool
>= Word8
65 Bool -> Bool -> Bool
&& Word8
w forall a. Ord a => a -> a -> Bool
<= Word8
90 = Word8
w forall a. Num a => a -> a -> a
+ Word8
32
| Bool
otherwise = Word8
w
stringCI :: ByteString -> Parser ByteString
stringCI :: ByteString -> Parser ByteString
stringCI ByteString
s = (forall r.
ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r)
-> (ByteString -> ByteString) -> ByteString -> Parser ByteString
string_ (forall r.
(ByteString -> ByteString)
-> ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
stringSuspended ByteString -> ByteString
lower) ByteString -> ByteString
lower ByteString
s
where lower :: ByteString -> ByteString
lower = (Word8 -> Word8) -> ByteString -> ByteString
B8.map Word8 -> Word8
toLower
{-# INLINE stringCI #-}
string_ :: (forall r. ByteString -> ByteString -> Buffer -> Pos -> More
-> Failure r -> Success ByteString r -> Result r)
-> (ByteString -> ByteString)
-> ByteString -> Parser ByteString
string_ :: (forall r.
ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r)
-> (ByteString -> ByteString) -> ByteString -> Parser ByteString
string_ forall r.
ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
suspended ByteString -> ByteString
f ByteString
s0 = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Success ByteString (State ByteString) ByteString r
succ ->
let n :: Int
n = ByteString -> Int
B.length ByteString
s
s :: ByteString
s = ByteString -> ByteString
f ByteString
s0
in if Pos -> Int -> Buffer -> Bool
lengthAtLeast Pos
pos Int
n State ByteString
t
then let t' :: ByteString
t' = Pos -> Pos -> Buffer -> ByteString
substring Pos
pos (Int -> Pos
Pos Int
n) State ByteString
t
in if ByteString
s forall a. Eq a => a -> a -> Bool
== ByteString -> ByteString
f ByteString
t'
then Success ByteString (State ByteString) ByteString r
succ State ByteString
t (Pos
pos forall a. Num a => a -> a -> a
+ Int -> Pos
Pos Int
n) More
more ByteString
t'
else Failure ByteString (State ByteString) r
lose State ByteString
t Pos
pos More
more [] [Char]
"string"
else let t' :: ByteString
t' = Int -> Buffer -> ByteString
Buf.unsafeDrop (Pos -> Int
fromPos Pos
pos) State ByteString
t
in if ByteString -> ByteString
f ByteString
t' ByteString -> ByteString -> Bool
`B.isPrefixOf` ByteString
s
then forall r.
ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
suspended ByteString
s (Int -> ByteString -> ByteString
B.drop (ByteString -> Int
B.length ByteString
t') ByteString
s) State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Success ByteString (State ByteString) ByteString r
succ
else Failure ByteString (State ByteString) r
lose State ByteString
t Pos
pos More
more [] [Char]
"string"
{-# INLINE string_ #-}
stringSuspended :: (ByteString -> ByteString)
-> ByteString -> ByteString -> Buffer -> Pos -> More
-> Failure r
-> Success ByteString r
-> Result r
stringSuspended :: forall r.
(ByteString -> ByteString)
-> ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
stringSuspended ByteString -> ByteString
f ByteString
s0 ByteString
s Buffer
t Pos
pos More
more Failure r
lose Success ByteString r
succ =
forall i a.
Parser i a
-> forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r
runParser (forall t. Chunk t => Parser t t
demandInput_ forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ByteString -> Parser ByteString
go) Buffer
t Pos
pos More
more Failure r
lose Success ByteString r
succ
where go :: ByteString -> Parser ByteString
go ByteString
s'0 = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t' Pos
pos' More
more' Failure ByteString (State ByteString) r
lose' Success ByteString (State ByteString) ByteString r
succ' ->
let m :: Int
m = ByteString -> Int
B.length ByteString
s
s' :: ByteString
s' = ByteString -> ByteString
f ByteString
s'0
n :: Int
n = ByteString -> Int
B.length ByteString
s'
in if Int
n forall a. Ord a => a -> a -> Bool
>= Int
m
then if Int -> ByteString -> ByteString
B.unsafeTake Int
m ByteString
s' forall a. Eq a => a -> a -> Bool
== ByteString
s
then let o :: Pos
o = Int -> Pos
Pos (ByteString -> Int
B.length ByteString
s0)
in Success ByteString (State ByteString) ByteString r
succ' State ByteString
t' (Pos
pos' forall a. Num a => a -> a -> a
+ Pos
o) More
more'
(Pos -> Pos -> Buffer -> ByteString
substring Pos
pos' Pos
o State ByteString
t')
else Failure ByteString (State ByteString) r
lose' State ByteString
t' Pos
pos' More
more' [] [Char]
"string"
else if ByteString
s' forall a. Eq a => a -> a -> Bool
== Int -> ByteString -> ByteString
B.unsafeTake Int
n ByteString
s
then forall r.
(ByteString -> ByteString)
-> ByteString
-> ByteString
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
stringSuspended ByteString -> ByteString
f ByteString
s0 (Int -> ByteString -> ByteString
B.unsafeDrop Int
n ByteString
s)
State ByteString
t' Pos
pos' More
more' Failure ByteString (State ByteString) r
lose' Success ByteString (State ByteString) ByteString r
succ'
else Failure ByteString (State ByteString) r
lose' State ByteString
t' Pos
pos' More
more' [] [Char]
"string"
skipWhile :: (Word8 -> Bool) -> Parser ()
skipWhile :: (Word8 -> Bool) -> Parser ()
skipWhile Word8 -> Bool
p = Parser ()
go
where
go :: Parser ()
go = do
ByteString
t <- (Word8 -> Bool) -> ByteString -> ByteString
B8.takeWhile Word8 -> Bool
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString
get
Bool
continue <- Int -> Parser Bool
inputSpansChunks (ByteString -> Int
B.length ByteString
t)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
continue Parser ()
go
{-# INLINE skipWhile #-}
takeTill :: (Word8 -> Bool) -> Parser ByteString
takeTill :: (Word8 -> Bool) -> Parser ByteString
takeTill Word8 -> Bool
p = (Word8 -> Bool) -> Parser ByteString
takeWhile (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
p)
{-# INLINE takeTill #-}
takeWhile :: (Word8 -> Bool) -> Parser ByteString
takeWhile :: (Word8 -> Bool) -> Parser ByteString
takeWhile Word8 -> Bool
p = do
ByteString
s <- (Word8 -> Bool) -> ByteString -> ByteString
B8.takeWhile Word8 -> Bool
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString
get
Bool
continue <- Int -> Parser Bool
inputSpansChunks (ByteString -> Int
B.length ByteString
s)
if Bool
continue
then (Word8 -> Bool) -> [ByteString] -> Parser ByteString
takeWhileAcc Word8 -> Bool
p [ByteString
s]
else forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
s
{-# INLINE takeWhile #-}
takeWhileAcc :: (Word8 -> Bool) -> [ByteString] -> Parser ByteString
takeWhileAcc :: (Word8 -> Bool) -> [ByteString] -> Parser ByteString
takeWhileAcc Word8 -> Bool
p = [ByteString] -> Parser ByteString
go
where
go :: [ByteString] -> Parser ByteString
go [ByteString]
acc = do
ByteString
s <- (Word8 -> Bool) -> ByteString -> ByteString
B8.takeWhile Word8 -> Bool
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString
get
Bool
continue <- Int -> Parser Bool
inputSpansChunks (ByteString -> Int
B.length ByteString
s)
if Bool
continue
then [ByteString] -> Parser ByteString
go (ByteString
sforall a. a -> [a] -> [a]
:[ByteString]
acc)
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall m. Monoid m => [m] -> m
concatReverse (ByteString
sforall a. a -> [a] -> [a]
:[ByteString]
acc)
{-# INLINE takeWhileAcc #-}
takeWhileIncluding :: (Word8 -> Bool) -> Parser B.ByteString
takeWhileIncluding :: (Word8 -> Bool) -> Parser ByteString
takeWhileIncluding Word8 -> Bool
p = do
(ByteString
s', ByteString
t) <- (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
B8.span Word8 -> Bool
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString
get
case ByteString -> Maybe (Word8, ByteString)
B8.uncons ByteString
t of
Just (Word8
h, ByteString
_) -> do
let s :: ByteString
s = ByteString
s' ByteString -> Word8 -> ByteString
`B8.snoc` Word8
h
Int -> Parser ()
advance (ByteString -> Int
B8.length ByteString
s)
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
s
Maybe (Word8, ByteString)
Nothing -> do
Bool
continue <- Int -> Parser Bool
inputSpansChunks (ByteString -> Int
B8.length ByteString
s')
if Bool
continue
then (Word8 -> Bool) -> [ByteString] -> Parser ByteString
takeWhileIncAcc Word8 -> Bool
p [ByteString
s']
else forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"takeWhileIncluding reached end of input"
{-# INLINE takeWhileIncluding #-}
takeWhileIncAcc :: (Word8 -> Bool) -> [B.ByteString] -> Parser B.ByteString
takeWhileIncAcc :: (Word8 -> Bool) -> [ByteString] -> Parser ByteString
takeWhileIncAcc Word8 -> Bool
p = [ByteString] -> Parser ByteString
go
where
go :: [ByteString] -> Parser ByteString
go [ByteString]
acc = do
(ByteString
s', ByteString
t) <- (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
B8.span Word8 -> Bool
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString
get
case ByteString -> Maybe (Word8, ByteString)
B8.uncons ByteString
t of
Just (Word8
h, ByteString
_) -> do
let s :: ByteString
s = ByteString
s' ByteString -> Word8 -> ByteString
`B8.snoc` Word8
h
Int -> Parser ()
advance (ByteString -> Int
B8.length ByteString
s)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall m. Monoid m => [m] -> m
concatReverse forall a b. (a -> b) -> a -> b
$ ByteString
sforall a. a -> [a] -> [a]
:[ByteString]
acc)
Maybe (Word8, ByteString)
Nothing -> do
Bool
continue <- Int -> Parser Bool
inputSpansChunks (ByteString -> Int
B8.length ByteString
s')
if Bool
continue
then [ByteString] -> Parser ByteString
go (ByteString
s'forall a. a -> [a] -> [a]
:[ByteString]
acc)
else forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"takeWhileIncAcc reached end of input"
{-# INLINE takeWhileIncAcc #-}
takeRest :: Parser [ByteString]
takeRest :: Parser [ByteString]
takeRest = [ByteString] -> Parser [ByteString]
go []
where
go :: [ByteString] -> Parser [ByteString]
go [ByteString]
acc = do
Bool
input <- forall t. Chunk t => Parser t Bool
wantInput
if Bool
input
then do
ByteString
s <- Parser ByteString
get
Int -> Parser ()
advance (ByteString -> Int
B.length ByteString
s)
[ByteString] -> Parser [ByteString]
go (ByteString
sforall a. a -> [a] -> [a]
:[ByteString]
acc)
else forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. [a] -> [a]
reverse [ByteString]
acc)
takeByteString :: Parser ByteString
takeByteString :: Parser ByteString
takeByteString = [ByteString] -> ByteString
B.concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Parser [ByteString]
takeRest
takeLazyByteString :: Parser L.ByteString
takeLazyByteString :: Parser ByteString
takeLazyByteString = [ByteString] -> ByteString
L.fromChunks forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Parser [ByteString]
takeRest
getChunk :: Parser (Maybe ByteString)
getChunk :: Parser (Maybe ByteString)
getChunk = do
Bool
input <- forall t. Chunk t => Parser t Bool
wantInput
if Bool
input
then forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString
get
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
data T s = T {-# UNPACK #-} !Int s
scan_ :: (s -> [ByteString] -> Parser r) -> s -> (s -> Word8 -> Maybe s)
-> Parser r
scan_ :: forall s r.
(s -> [ByteString] -> Parser r)
-> s -> (s -> Word8 -> Maybe s) -> Parser r
scan_ s -> [ByteString] -> Parser r
f s
s0 s -> Word8 -> Maybe s
p = [ByteString] -> s -> Parser r
go [] s
s0
where
go :: [ByteString] -> s -> Parser r
go [ByteString]
acc s
s1 = do
let scanner :: ByteString -> IO (T s)
scanner ByteString
bs = forall r. ByteString -> (ForeignPtr Word8 -> Int -> Int -> r) -> r
withPS ByteString
bs forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp Int
off Int
len ->
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr0 -> do
let start :: Ptr Word8
start = Ptr Word8
ptr0 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
off
end :: Ptr Word8
end = Ptr Word8
start forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len
inner :: Ptr Word8 -> s -> IO (T s)
inner Ptr Word8
ptr !s
s
| Ptr Word8
ptr forall a. Ord a => a -> a -> Bool
< Ptr Word8
end = do
Word8
w <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr
case s -> Word8 -> Maybe s
p s
s Word8
w of
Just s
s' -> Ptr Word8 -> s -> IO (T s)
inner (Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) s
s'
Maybe s
_ -> forall {m :: * -> *} {s}. Monad m => Int -> s -> m (T s)
done (Ptr Word8
ptr forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
start) s
s
| Bool
otherwise = forall {m :: * -> *} {s}. Monad m => Int -> s -> m (T s)
done (Ptr Word8
ptr forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
start) s
s
done :: Int -> s -> m (T s)
done !Int
i !s
s = forall (m :: * -> *) a. Monad m => a -> m a
return (forall s. Int -> s -> T s
T Int
i s
s)
Ptr Word8 -> s -> IO (T s)
inner Ptr Word8
start s
s1
ByteString
bs <- Parser ByteString
get
let T Int
i s
s' = forall a. IO a -> a
inlinePerformIO forall a b. (a -> b) -> a -> b
$ ByteString -> IO (T s)
scanner ByteString
bs
!h :: ByteString
h = Int -> ByteString -> ByteString
B.unsafeTake Int
i ByteString
bs
Bool
continue <- Int -> Parser Bool
inputSpansChunks Int
i
if Bool
continue
then [ByteString] -> s -> Parser r
go (ByteString
hforall a. a -> [a] -> [a]
:[ByteString]
acc) s
s'
else s -> [ByteString] -> Parser r
f s
s' (ByteString
hforall a. a -> [a] -> [a]
:[ByteString]
acc)
{-# INLINE scan_ #-}
scan :: s -> (s -> Word8 -> Maybe s) -> Parser ByteString
scan :: forall s. s -> (s -> Word8 -> Maybe s) -> Parser ByteString
scan = forall s r.
(s -> [ByteString] -> Parser r)
-> s -> (s -> Word8 -> Maybe s) -> Parser r
scan_ forall a b. (a -> b) -> a -> b
$ \s
_ [ByteString]
chunks -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! forall m. Monoid m => [m] -> m
concatReverse [ByteString]
chunks
{-# INLINE scan #-}
runScanner :: s -> (s -> Word8 -> Maybe s) -> Parser (ByteString, s)
runScanner :: forall s. s -> (s -> Word8 -> Maybe s) -> Parser (ByteString, s)
runScanner = forall s r.
(s -> [ByteString] -> Parser r)
-> s -> (s -> Word8 -> Maybe s) -> Parser r
scan_ forall a b. (a -> b) -> a -> b
$ \s
s [ByteString]
xs -> let !sx :: ByteString
sx = forall m. Monoid m => [m] -> m
concatReverse [ByteString]
xs in forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
sx, s
s)
{-# INLINE runScanner #-}
takeWhile1 :: (Word8 -> Bool) -> Parser ByteString
takeWhile1 :: (Word8 -> Bool) -> Parser ByteString
takeWhile1 Word8 -> Bool
p = do
(forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` forall t. Chunk t => Parser t ()
demandInput) forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Parser Bool
endOfChunk
ByteString
s <- (Word8 -> Bool) -> ByteString -> ByteString
B8.takeWhile Word8 -> Bool
p forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ByteString
get
let len :: Int
len = ByteString -> Int
B.length ByteString
s
if Int
len forall a. Eq a => a -> a -> Bool
== Int
0
then forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
"takeWhile1"
else do
Int -> Parser ()
advance Int
len
Bool
eoc <- Parser Bool
endOfChunk
if Bool
eoc
then (Word8 -> Bool) -> [ByteString] -> Parser ByteString
takeWhileAcc Word8 -> Bool
p [ByteString
s]
else forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
s
{-# INLINE takeWhile1 #-}
inClass :: String -> Word8 -> Bool
inClass :: [Char] -> Word8 -> Bool
inClass [Char]
s = (Word8 -> FastSet -> Bool
`memberWord8` FastSet
mySet)
where mySet :: FastSet
mySet = [Char] -> FastSet
charClass [Char]
s
{-# NOINLINE mySet #-}
{-# INLINE inClass #-}
notInClass :: String -> Word8 -> Bool
notInClass :: [Char] -> Word8 -> Bool
notInClass [Char]
s = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Word8 -> Bool
inClass [Char]
s
{-# INLINE notInClass #-}
anyWord8 :: Parser Word8
anyWord8 :: Parser Word8
anyWord8 = (Word8 -> Bool) -> Parser Word8
satisfy forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const Bool
True
{-# INLINE anyWord8 #-}
word8 :: Word8 -> Parser Word8
word8 :: Word8 -> Parser Word8
word8 Word8
c = (Word8 -> Bool) -> Parser Word8
satisfy (forall a. Eq a => a -> a -> Bool
== Word8
c) forall i a. Parser i a -> [Char] -> Parser i a
<?> forall a. Show a => a -> [Char]
show Word8
c
{-# INLINE word8 #-}
notWord8 :: Word8 -> Parser Word8
notWord8 :: Word8 -> Parser Word8
notWord8 Word8
c = (Word8 -> Bool) -> Parser Word8
satisfy (forall a. Eq a => a -> a -> Bool
/= Word8
c) forall i a. Parser i a -> [Char] -> Parser i a
<?> [Char]
"not " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Word8
c
{-# INLINE notWord8 #-}
peekWord8 :: Parser (Maybe Word8)
peekWord8 :: Parser (Maybe Word8)
peekWord8 = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t pos :: Pos
pos@(Pos Int
pos_) More
more Failure ByteString (State ByteString) r
_lose Success ByteString (State ByteString) (Maybe Word8) r
succ ->
case () of
()
_| Int
pos_ forall a. Ord a => a -> a -> Bool
< Buffer -> Int
Buf.length State ByteString
t ->
let !w :: Word8
w = Buffer -> Int -> Word8
Buf.unsafeIndex State ByteString
t Int
pos_
in Success ByteString (State ByteString) (Maybe Word8) r
succ State ByteString
t Pos
pos More
more (forall a. a -> Maybe a
Just Word8
w)
| More
more forall a. Eq a => a -> a -> Bool
== More
Complete ->
Success ByteString (State ByteString) (Maybe Word8) r
succ State ByteString
t Pos
pos More
more forall a. Maybe a
Nothing
| Bool
otherwise ->
let succ' :: Buffer -> Pos -> More -> IResult ByteString r
succ' Buffer
t' Pos
pos' More
more' = let !w :: Word8
w = Buffer -> Int -> Word8
Buf.unsafeIndex Buffer
t' Int
pos_
in Success ByteString (State ByteString) (Maybe Word8) r
succ Buffer
t' Pos
pos' More
more' (forall a. a -> Maybe a
Just Word8
w)
lose' :: Buffer -> Pos -> More -> IResult ByteString r
lose' Buffer
t' Pos
pos' More
more' = Success ByteString (State ByteString) (Maybe Word8) r
succ Buffer
t' Pos
pos' More
more' forall a. Maybe a
Nothing
in forall t r.
Chunk t =>
State t
-> Pos
-> More
-> (State t -> Pos -> More -> IResult t r)
-> (State t -> Pos -> More -> IResult t r)
-> IResult t r
prompt State ByteString
t Pos
pos More
more Buffer -> Pos -> More -> IResult ByteString r
lose' Buffer -> Pos -> More -> IResult ByteString r
succ'
{-# INLINE peekWord8 #-}
peekWord8' :: Parser Word8
peekWord8' :: Parser Word8
peekWord8' = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Success ByteString (State ByteString) Word8 r
succ ->
if Pos -> Int -> Buffer -> Bool
lengthAtLeast Pos
pos Int
1 State ByteString
t
then Success ByteString (State ByteString) Word8 r
succ State ByteString
t Pos
pos More
more (Buffer -> Int -> Word8
Buf.unsafeIndex State ByteString
t (Pos -> Int
fromPos Pos
pos))
else let succ' :: Buffer -> Pos -> More -> ByteString -> IResult ByteString r
succ' Buffer
t' Pos
pos' More
more' ByteString
bs' = Success ByteString (State ByteString) Word8 r
succ Buffer
t' Pos
pos' More
more' forall a b. (a -> b) -> a -> b
$! ByteString -> Word8
B.unsafeHead ByteString
bs'
in forall r.
Int
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
ensureSuspended Int
1 State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Buffer -> Pos -> More -> ByteString -> IResult ByteString r
succ'
{-# INLINE peekWord8' #-}
endOfLine :: Parser ()
endOfLine :: Parser ()
endOfLine = (Word8 -> Parser Word8
word8 Word8
10 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (ByteString -> Parser ByteString
string ByteString
"\r\n" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ())
failK :: Failure a
failK :: forall a. Failure a
failK Buffer
t (Pos Int
pos) More
_more [[Char]]
stack [Char]
msg = forall i r. i -> [[Char]] -> [Char] -> IResult i r
Fail (Int -> Buffer -> ByteString
Buf.unsafeDrop Int
pos Buffer
t) [[Char]]
stack [Char]
msg
{-# INLINE failK #-}
successK :: Success a a
successK :: forall a. Success a a
successK Buffer
t (Pos Int
pos) More
_more a
a = forall i r. i -> r -> IResult i r
Done (Int -> Buffer -> ByteString
Buf.unsafeDrop Int
pos Buffer
t) a
a
{-# INLINE successK #-}
parse :: Parser a -> ByteString -> Result a
parse :: forall a. Parser a -> ByteString -> Result a
parse Parser a
m ByteString
s = forall i a.
Parser i a
-> forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r
T.runParser Parser a
m (ByteString -> Buffer
buffer ByteString
s) (Int -> Pos
Pos Int
0) More
Incomplete forall a. Failure a
failK forall a. Success a a
successK
{-# INLINE parse #-}
parseOnly :: Parser a -> ByteString -> Either String a
parseOnly :: forall a. Parser a -> ByteString -> Either [Char] a
parseOnly Parser a
m ByteString
s = case forall i a.
Parser i a
-> forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r
T.runParser Parser a
m (ByteString -> Buffer
buffer ByteString
s) (Int -> Pos
Pos Int
0) More
Complete forall a. Failure a
failK forall a. Success a a
successK of
Fail ByteString
_ [] [Char]
err -> forall a b. a -> Either a b
Left [Char]
err
Fail ByteString
_ [[Char]]
ctxs [Char]
err -> forall a b. a -> Either a b
Left (forall a. [a] -> [[a]] -> [a]
intercalate [Char]
" > " [[Char]]
ctxs forall a. [a] -> [a] -> [a]
++ [Char]
": " forall a. [a] -> [a] -> [a]
++ [Char]
err)
Done ByteString
_ a
a -> forall a b. b -> Either a b
Right a
a
IResult ByteString a
_ -> forall a. HasCallStack => [Char] -> a
error [Char]
"parseOnly: impossible error!"
{-# INLINE parseOnly #-}
get :: Parser ByteString
get :: Parser ByteString
get = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
_lose Success ByteString (State ByteString) ByteString r
succ ->
Success ByteString (State ByteString) ByteString r
succ State ByteString
t Pos
pos More
more (Int -> Buffer -> ByteString
Buf.unsafeDrop (Pos -> Int
fromPos Pos
pos) State ByteString
t)
{-# INLINE get #-}
endOfChunk :: Parser Bool
endOfChunk :: Parser Bool
endOfChunk = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
_lose Success ByteString (State ByteString) Bool r
succ ->
Success ByteString (State ByteString) Bool r
succ State ByteString
t Pos
pos More
more (Pos -> Int
fromPos Pos
pos forall a. Eq a => a -> a -> Bool
== Buffer -> Int
Buf.length State ByteString
t)
{-# INLINE endOfChunk #-}
inputSpansChunks :: Int -> Parser Bool
inputSpansChunks :: Int -> Parser Bool
inputSpansChunks Int
i = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos_ More
more Failure ByteString (State ByteString) r
_lose Success ByteString (State ByteString) Bool r
succ ->
let pos :: Pos
pos = Pos
pos_ forall a. Num a => a -> a -> a
+ Int -> Pos
Pos Int
i
in if Pos -> Int
fromPos Pos
pos forall a. Ord a => a -> a -> Bool
< Buffer -> Int
Buf.length State ByteString
t Bool -> Bool -> Bool
|| More
more forall a. Eq a => a -> a -> Bool
== More
Complete
then Success ByteString (State ByteString) Bool r
succ State ByteString
t Pos
pos More
more Bool
False
else let lose' :: Buffer -> Pos -> More -> IResult ByteString r
lose' Buffer
t' Pos
pos' More
more' = Success ByteString (State ByteString) Bool r
succ Buffer
t' Pos
pos' More
more' Bool
False
succ' :: Buffer -> Pos -> More -> IResult ByteString r
succ' Buffer
t' Pos
pos' More
more' = Success ByteString (State ByteString) Bool r
succ Buffer
t' Pos
pos' More
more' Bool
True
in forall t r.
Chunk t =>
State t
-> Pos
-> More
-> (State t -> Pos -> More -> IResult t r)
-> (State t -> Pos -> More -> IResult t r)
-> IResult t r
prompt State ByteString
t Pos
pos More
more Buffer -> Pos -> More -> IResult ByteString r
lose' Buffer -> Pos -> More -> IResult ByteString r
succ'
{-# INLINE inputSpansChunks #-}
advance :: Int -> Parser ()
advance :: Int -> Parser ()
advance Int
n = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
_lose Success ByteString (State ByteString) () r
succ ->
Success ByteString (State ByteString) () r
succ State ByteString
t (Pos
pos forall a. Num a => a -> a -> a
+ Int -> Pos
Pos Int
n) More
more ()
{-# INLINE advance #-}
ensureSuspended :: Int -> Buffer -> Pos -> More
-> Failure r
-> Success ByteString r
-> Result r
ensureSuspended :: forall r.
Int
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
ensureSuspended Int
n Buffer
t Pos
pos More
more Failure r
lose Success ByteString r
succ =
forall i a.
Parser i a
-> forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r
runParser (forall t. Chunk t => Parser t ()
demandInput forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser ByteString
go) Buffer
t Pos
pos More
more Failure r
lose Success ByteString r
succ
where go :: Parser ByteString
go = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t' Pos
pos' More
more' Failure ByteString (State ByteString) r
lose' Success ByteString (State ByteString) ByteString r
succ' ->
if Pos -> Int -> Buffer -> Bool
lengthAtLeast Pos
pos' Int
n State ByteString
t'
then Success ByteString (State ByteString) ByteString r
succ' State ByteString
t' Pos
pos' More
more' (Pos -> Pos -> Buffer -> ByteString
substring Pos
pos (Int -> Pos
Pos Int
n) State ByteString
t')
else forall i a.
Parser i a
-> forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r
runParser (forall t. Chunk t => Parser t ()
demandInput forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser ByteString
go) State ByteString
t' Pos
pos' More
more' Failure ByteString (State ByteString) r
lose' Success ByteString (State ByteString) ByteString r
succ'
ensure :: Int -> Parser ByteString
ensure :: Int -> Parser ByteString
ensure Int
n = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Success ByteString (State ByteString) ByteString r
succ ->
if Pos -> Int -> Buffer -> Bool
lengthAtLeast Pos
pos Int
n State ByteString
t
then Success ByteString (State ByteString) ByteString r
succ State ByteString
t Pos
pos More
more (Pos -> Pos -> Buffer -> ByteString
substring Pos
pos (Int -> Pos
Pos Int
n) State ByteString
t)
else forall r.
Int
-> Buffer
-> Pos
-> More
-> Failure r
-> Success ByteString r
-> Result r
ensureSuspended Int
n State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Success ByteString (State ByteString) ByteString r
succ
{-# INLINE ensure #-}
match :: Parser a -> Parser (ByteString, a)
match :: forall a. Parser a -> Parser (ByteString, a)
match Parser a
p = forall i a.
(forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r)
-> Parser i a
T.Parser forall a b. (a -> b) -> a -> b
$ \State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Success ByteString (State ByteString) (ByteString, a) r
succ ->
let succ' :: Buffer -> Pos -> More -> a -> IResult ByteString r
succ' Buffer
t' Pos
pos' More
more' a
a =
Success ByteString (State ByteString) (ByteString, a) r
succ Buffer
t' Pos
pos' More
more' (Pos -> Pos -> Buffer -> ByteString
substring Pos
pos (Pos
pos'forall a. Num a => a -> a -> a
-Pos
pos) Buffer
t', a
a)
in forall i a.
Parser i a
-> forall r.
State i
-> Pos
-> More
-> Failure i (State i) r
-> Success i (State i) a r
-> IResult i r
runParser Parser a
p State ByteString
t Pos
pos More
more Failure ByteString (State ByteString) r
lose Buffer -> Pos -> More -> a -> IResult ByteString r
succ'
lengthAtLeast :: Pos -> Int -> Buffer -> Bool
lengthAtLeast :: Pos -> Int -> Buffer -> Bool
lengthAtLeast (Pos Int
pos) Int
n Buffer
bs = Buffer -> Int
Buf.length Buffer
bs forall a. Ord a => a -> a -> Bool
>= Int
pos forall a. Num a => a -> a -> a
+ Int
n
{-# INLINE lengthAtLeast #-}
substring :: Pos -> Pos -> Buffer -> ByteString
substring :: Pos -> Pos -> Buffer -> ByteString
substring (Pos Int
pos) (Pos Int
n) = Int -> Int -> Buffer -> ByteString
Buf.substring Int
pos Int
n
{-# INLINE substring #-}