module Z.Data.Parser.Base
(
Result(..)
, ParseError
, ParseStep
, Parser(..)
, (<?>)
, parse, parse', parseChunk, ParseChunks, parseChunks, finishParsing
, runAndKeepTrack, match
, ensureN, endOfInput, currentChunk, atEnd
, decodePrim, BE(..), LE(..)
, decodePrimLE, decodePrimBE
, scan, scanChunks, peekMaybe, peek, satisfy, satisfyWith
, anyWord8, word8, char8, anyChar8, anyCharUTF8, charUTF8, char7, anyChar7
, skipWord8, endOfLine, skip, skipWhile, skipSpaces
, take, takeN, takeTill, takeWhile, takeWhile1, takeRemaining, bytes, bytesCI
, text
, fail', failWithInput, unsafeLiftIO
, decodeWord , decodeWord64, decodeWord32, decodeWord16, decodeWord8
, decodeInt , decodeInt64 , decodeInt32 , decodeInt16 , decodeInt8 , decodeDouble, decodeFloat
, decodeWordLE , decodeWord64LE , decodeWord32LE , decodeWord16LE
, decodeIntLE , decodeInt64LE , decodeInt32LE , decodeInt16LE , decodeDoubleLE , decodeFloatLE
, decodeWordBE , decodeWord64BE , decodeWord32BE , decodeWord16BE
, decodeIntBE , decodeInt64BE , decodeInt32BE , decodeInt16BE , decodeDoubleBE , decodeFloatBE
) where
import Control.Applicative
import Control.Monad
import Control.Monad.Primitive
import qualified Control.Monad.Fail as Fail
import qualified Data.CaseInsensitive as CI
import qualified Data.Primitive.PrimArray as A
import Data.Int
import Data.Word
import Data.Bits ((.&.))
import GHC.Types
import GHC.Exts (State#, runRW#, unsafeCoerce#)
import Prelude hiding (take, takeWhile, decodeFloat)
import Z.Data.Array.Unaligned
import Z.Data.ASCII
import qualified Z.Data.Text as T
import qualified Z.Data.Text.Base as T
import qualified Z.Data.Text.UTF8Codec as T
import qualified Z.Data.Vector.Base as V
import qualified Z.Data.Vector.Extra as V
data Result e r
= Success r !V.Bytes
| Failure e !V.Bytes
| Partial (ParseStep e r)
type ParseStep e r = V.Bytes -> Result e r
type ParseError = [T.Text]
instance Functor (Result e) where
fmap :: (a -> b) -> Result e a -> Result e b
fmap a -> b
f (Success a
a Bytes
s) = b -> Bytes -> Result e b
forall e r. r -> Bytes -> Result e r
Success (a -> b
f a
a) Bytes
s
fmap a -> b
f (Partial ParseStep e a
k) = (Bytes -> Result e b) -> Result e b
forall e r. (Bytes -> Result e r) -> Result e r
Partial ((a -> b) -> Result e a -> Result e b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Result e a -> Result e b) -> ParseStep e a -> Bytes -> Result e b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ParseStep e a
k)
fmap a -> b
_ (Failure e
e Bytes
v) = e -> Bytes -> Result e b
forall e r. e -> Bytes -> Result e r
Failure e
e Bytes
v
instance (Show e, Show a) => Show (Result e a) where
show :: Result e a -> String
show (Success a
a Bytes
_) = String
"Success " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
a
show (Partial ParseStep e a
_) = String
"Partial _"
show (Failure e
errs Bytes
_) = String
"Failure: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ e -> String
forall a. Show a => a -> String
show e
errs
newtype Parser a = Parser {
Parser a
-> forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
runParser :: forall r . (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState -> ParseStep ParseError r
}
data ParserState
instance Functor Parser where
fmap :: (a -> b) -> Parser a -> Parser b
fmap a -> b
f (Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa) = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser b
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s' -> State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s' (b -> ParseStep ParseError r)
-> (a -> b) -> a -> ParseStep ParseError r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) State# ParserState
s Bytes
inp)
{-# INLINE fmap #-}
a
a <$ :: a -> Parser b -> Parser a
<$ Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pb = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pb ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s' b
_ -> State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s' a
a) State# ParserState
s Bytes
inp)
{-# INLINE (<$) #-}
instance Applicative Parser where
pure :: a -> Parser a
pure a
x = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s a
x Bytes
inp)
{-# INLINE pure #-}
Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> (a -> b) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pf <*> :: Parser (a -> b) -> Parser a -> Parser b
<*> Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser b
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> (a -> b) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> (a -> b) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pf ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s' a -> b
f -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s'' -> State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s'' (b -> ParseStep ParseError r)
-> (a -> b) -> a -> ParseStep ParseError r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) State# ParserState
s') State# ParserState
s Bytes
inp)
{-# INLINE (<*>) #-}
Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa *> :: Parser a -> Parser b -> Parser b
*> Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pb = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser b
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s' a
_ -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pb ParseError -> ParseStep ParseError r
kf State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s') State# ParserState
s Bytes
inp)
{-# INLINE (*>) #-}
Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa <* :: Parser a -> Parser b -> Parser a
<* Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pb = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s' a
x -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pb ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s'' b
_ -> State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s'' a
x) State# ParserState
s') State# ParserState
s Bytes
inp)
{-# INLINE (<*) #-}
instance Monad Parser where
return :: a -> Parser a
return = a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE return #-}
Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa >>= :: Parser a -> (a -> Parser b) -> Parser b
>>= a -> Parser b
f = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser b
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa ParseError -> ParseStep ParseError r
kf (\ State# ParserState
s' a
a -> Parser b
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> b -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall a.
Parser a
-> forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
runParser (a -> Parser b
f a
a) ParseError -> ParseStep ParseError r
kf State# ParserState -> b -> ParseStep ParseError r
k State# ParserState
s') State# ParserState
s Bytes
inp)
{-# INLINE (>>=) #-}
>> :: Parser a -> Parser b -> Parser b
(>>) = Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
{-# INLINE (>>) #-}
instance PrimMonad Parser where
type PrimState Parser = ParserState
{-# INLINE primitive #-}
primitive :: (State# (PrimState Parser) -> (# State# (PrimState Parser), a #))
-> Parser a
primitive State# (PrimState Parser) -> (# State# (PrimState Parser), a #)
io = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
st Bytes
inp ->
let !(# State# ParserState
st', a
r #) = State# (PrimState Parser) -> (# State# (PrimState Parser), a #)
io State# (PrimState Parser)
State# ParserState
st
in State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
st' a
r Bytes
inp)
{-# RULES "replicateM/Parser" forall n (x :: Parser a). V.replicateM n x = V.replicatePM n x #-}
{-# RULES "traverse/Parser" forall (f :: a -> Parser b). V.traverse f = V.traverseWithIndexPM (const f) #-}
{-# RULES "traverseWithIndex/Parser" forall (f :: Int -> a -> Parser b). V.traverseWithIndex f = V.traverseWithIndexPM f #-}
unsafeLiftIO :: IO a -> Parser a
{-# INLINE unsafeLiftIO #-}
unsafeLiftIO :: IO a -> Parser a
unsafeLiftIO (IO State# RealWorld -> (# State# RealWorld, a #)
io) = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a)
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
_ State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
st Bytes
inp ->
let !(# State# RealWorld
st', a
r #) = State# RealWorld -> (# State# RealWorld, a #)
io (State# ParserState -> State# RealWorld
unsafeCoerce# State# ParserState
st)
in State# ParserState -> a -> ParseStep ParseError r
k (State# RealWorld -> State# ParserState
unsafeCoerce# State# RealWorld
st') a
r Bytes
inp
instance Fail.MonadFail Parser where
fail :: String -> Parser a
fail = Text -> Parser a
forall a. Text -> Parser a
fail' (Text -> Parser a) -> (String -> Text) -> String -> Parser a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
{-# INLINE fail #-}
instance MonadPlus Parser where
mzero :: Parser a
mzero = Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
{-# INLINE mzero #-}
mplus :: Parser a -> Parser a -> Parser a
mplus = Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
{-# INLINE mplus #-}
instance Alternative Parser where
empty :: Parser a
empty = Text -> Parser a
forall a. Text -> Parser a
fail' Text
"Z.Data.Parser.Base(Alternative).empty"
{-# INLINE empty #-}
Parser a
f <|> :: Parser a -> Parser a -> Parser a
<|> Parser a
g = do
(Result ParseError a
r, [Bytes]
bss) <- Parser a -> Parser (Result ParseError a, [Bytes])
forall a. Parser a -> Parser (Result ParseError a, [Bytes])
runAndKeepTrack Parser a
f
case Result ParseError a
r of
Success a
x Bytes
inp -> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
_ -> State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s a
x Bytes
inp)
Failure ParseError
_ Bytes
_ -> let !bs :: Bytes
bs = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
bss)
in (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
_ -> Parser a
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall a.
Parser a
-> forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
runParser Parser a
g ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
bs)
Result ParseError a
_ -> String -> Parser a
forall a. HasCallStack => String -> a
error String
"Z.Data.Parser.Base: impossible"
{-# INLINE (<|>) #-}
fail' :: T.Text -> Parser a
{-# INLINE fail' #-}
fail' :: Text -> Parser a
fail' Text
msg = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
_ State# ParserState
_ Bytes
inp -> ParseError -> ParseStep ParseError r
kf [Text
msg] Bytes
inp)
failWithInput :: (V.Bytes -> T.Text) -> Parser a
{-# INLINE failWithInput #-}
failWithInput :: (Bytes -> Text) -> Parser a
failWithInput Bytes -> Text
f = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
_ State# ParserState
_ Bytes
inp -> ParseError -> ParseStep ParseError r
kf [Bytes -> Text
f Bytes
inp] Bytes
inp)
parse' :: Parser a -> V.Bytes -> Either ParseError a
{-# INLINE parse' #-}
parse' :: Parser a -> Bytes -> Either ParseError a
parse' (Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p) Bytes
inp = (Bytes, Either ParseError a) -> Either ParseError a
forall a b. (a, b) -> b
snd ((Bytes, Either ParseError a) -> Either ParseError a)
-> (Bytes, Either ParseError a) -> Either ParseError a
forall a b. (a -> b) -> a -> b
$ Result ParseError a -> (Bytes, Either ParseError a)
forall a. Result ParseError a -> (Bytes, Either ParseError a)
finishParsing ((State# RealWorld -> Result ParseError a) -> Result ParseError a
forall o. (State# RealWorld -> o) -> o
runRW# (\ State# RealWorld
s ->
Result ParseError a -> Result ParseError a
unsafeCoerce# ((ParseError -> ParseStep ParseError a)
-> (State# ParserState -> a -> ParseStep ParseError a)
-> State# ParserState
-> ParseStep ParseError a
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p ParseError -> ParseStep ParseError a
forall e r. e -> Bytes -> Result e r
Failure (\ State# ParserState
_ a
r -> a -> ParseStep ParseError a
forall e r. r -> Bytes -> Result e r
Success a
r) (State# RealWorld -> State# ParserState
unsafeCoerce# State# RealWorld
s) Bytes
inp)))
parse :: Parser a -> V.Bytes -> (V.Bytes, Either ParseError a)
{-# INLINE parse #-}
parse :: Parser a -> Bytes -> (Bytes, Either ParseError a)
parse (Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p) Bytes
inp = Result ParseError a -> (Bytes, Either ParseError a)
forall a. Result ParseError a -> (Bytes, Either ParseError a)
finishParsing ((State# RealWorld -> Result ParseError a) -> Result ParseError a
forall o. (State# RealWorld -> o) -> o
runRW# ( \ State# RealWorld
s ->
Result ParseError a -> Result ParseError a
unsafeCoerce# ((ParseError -> ParseStep ParseError a)
-> (State# ParserState -> a -> ParseStep ParseError a)
-> State# ParserState
-> ParseStep ParseError a
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p ParseError -> ParseStep ParseError a
forall e r. e -> Bytes -> Result e r
Failure (\ State# ParserState
_ a
r -> a -> ParseStep ParseError a
forall e r. r -> Bytes -> Result e r
Success a
r) (State# RealWorld -> State# ParserState
unsafeCoerce# State# RealWorld
s) Bytes
inp)))
parseChunk :: Parser a -> V.Bytes -> Result ParseError a
{-# INLINE parseChunk #-}
parseChunk :: Parser a -> Bytes -> Result ParseError a
parseChunk (Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p) = (State# RealWorld -> Bytes -> Result ParseError a)
-> Bytes -> Result ParseError a
forall o. (State# RealWorld -> o) -> o
runRW# (\ State# RealWorld
s ->
(Bytes -> Result ParseError a) -> Bytes -> Result ParseError a
unsafeCoerce# ((ParseError -> Bytes -> Result ParseError a)
-> (State# ParserState -> a -> Bytes -> Result ParseError a)
-> State# ParserState
-> Bytes
-> Result ParseError a
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p ParseError -> Bytes -> Result ParseError a
forall e r. e -> Bytes -> Result e r
Failure (\ State# ParserState
_ a
r -> a -> Bytes -> Result ParseError a
forall e r. r -> Bytes -> Result e r
Success a
r) (State# RealWorld -> State# ParserState
unsafeCoerce# State# RealWorld
s)))
finishParsing :: Result ParseError a -> (V.Bytes, Either ParseError a)
{-# INLINABLE finishParsing #-}
finishParsing :: Result ParseError a -> (Bytes, Either ParseError a)
finishParsing Result ParseError a
r = case Result ParseError a
r of
Success a
a Bytes
rest -> (Bytes
rest, a -> Either ParseError a
forall a b. b -> Either a b
Right a
a)
Failure ParseError
errs Bytes
rest -> (Bytes
rest, ParseError -> Either ParseError a
forall a b. a -> Either a b
Left ParseError
errs)
Partial ParseStep ParseError a
f -> Result ParseError a -> (Bytes, Either ParseError a)
forall a. Result ParseError a -> (Bytes, Either ParseError a)
finishParsing (ParseStep ParseError a
f Bytes
forall (v :: * -> *) a. Vec v a => v a
V.empty)
type ParseChunks m err x = m V.Bytes -> V.Bytes -> m (V.Bytes, Either err x)
parseChunks :: Monad m => (V.Bytes -> Result e a) -> ParseChunks m e a
{-# INLINABLE parseChunks #-}
parseChunks :: (Bytes -> Result e a) -> ParseChunks m e a
parseChunks Bytes -> Result e a
pc m Bytes
m Bytes
inp = Result e a -> m (Bytes, Either e a)
go (Bytes -> Result e a
pc Bytes
inp)
where
go :: Result e a -> m (Bytes, Either e a)
go Result e a
r = case Result e a
r of
Partial Bytes -> Result e a
f -> Result e a -> m (Bytes, Either e a)
go (Result e a -> m (Bytes, Either e a))
-> (Bytes -> Result e a) -> Bytes -> m (Bytes, Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bytes -> Result e a
f (Bytes -> m (Bytes, Either e a))
-> m Bytes -> m (Bytes, Either e a)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m Bytes
m
Success a
a Bytes
rest -> (Bytes, Either e a) -> m (Bytes, Either e a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bytes
rest, a -> Either e a
forall a b. b -> Either a b
Right a
a)
Failure e
errs Bytes
rest -> (Bytes, Either e a) -> m (Bytes, Either e a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bytes
rest, e -> Either e a
forall a b. a -> Either a b
Left e
errs)
(<?>) :: T.Text -> Parser a -> Parser a
{-# INLINE (<?>) #-}
Text
msg <?> :: Text -> Parser a -> Parser a
<?> (Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p) = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
p (ParseError -> ParseStep ParseError r
kf (ParseError -> ParseStep ParseError r)
-> (ParseError -> ParseError)
-> ParseError
-> ParseStep ParseError r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
msgText -> ParseError -> ParseError
forall k1. k1 -> [k1] -> [k1]
:)) State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
inp)
infixr 0 <?>
runAndKeepTrack :: Parser a -> Parser (Result ParseError a, [V.Bytes])
{-# INLINE runAndKeepTrack #-}
runAndKeepTrack :: Parser a -> Parser (Result ParseError a, [Bytes])
runAndKeepTrack (Parser forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa) = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState
-> (Result ParseError a, [Bytes]) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Result ParseError a, [Bytes])
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState
-> (Result ParseError a, [Bytes]) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Result ParseError a, [Bytes]))
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState
-> (Result ParseError a, [Bytes]) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Result ParseError a, [Bytes])
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
_ State# ParserState
-> (Result ParseError a, [Bytes]) -> ParseStep ParseError r
k0 State# ParserState
st0 Bytes
inp ->
let go :: [Bytes]
-> Result e r
-> (State# ParserState
-> (Result e r, [Bytes]) -> Bytes -> Result e r)
-> State# ParserState
-> Result e r
go ![Bytes]
acc Result e r
r State# ParserState -> (Result e r, [Bytes]) -> Bytes -> Result e r
k (State# ParserState
st :: State# ParserState) = case Result e r
r of
Partial ParseStep e r
k' -> (Bytes -> Result e r) -> Result e r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (\ Bytes
inp' -> [Bytes]
-> Result e r
-> (State# ParserState
-> (Result e r, [Bytes]) -> Bytes -> Result e r)
-> State# ParserState
-> Result e r
go (Bytes
inp'Bytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
:[Bytes]
acc) (ParseStep e r
k' Bytes
inp') State# ParserState -> (Result e r, [Bytes]) -> Bytes -> Result e r
k State# ParserState
st)
Success r
_ Bytes
inp' -> State# ParserState -> (Result e r, [Bytes]) -> Bytes -> Result e r
k State# ParserState
st (Result e r
r, [Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc) Bytes
inp'
Failure e
_ Bytes
inp' -> State# ParserState -> (Result e r, [Bytes]) -> Bytes -> Result e r
k State# ParserState
st (Result e r
r, [Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc) Bytes
inp'
r0 :: Result ParseError a
r0 = (State# RealWorld -> Result ParseError a) -> Result ParseError a
forall o. (State# RealWorld -> o) -> o
runRW# (\ State# RealWorld
s ->
Result ParseError a -> Result ParseError a
unsafeCoerce# ((ParseError -> ParseStep ParseError a)
-> (State# ParserState -> a -> ParseStep ParseError a)
-> State# ParserState
-> ParseStep ParseError a
forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
pa ParseError -> ParseStep ParseError a
forall e r. e -> Bytes -> Result e r
Failure (\ State# ParserState
_ a
r -> a -> ParseStep ParseError a
forall e r. r -> Bytes -> Result e r
Success a
r) (State# RealWorld -> State# ParserState
unsafeCoerce# State# RealWorld
s) Bytes
inp))
in [Bytes]
-> Result ParseError a
-> (State# ParserState
-> (Result ParseError a, [Bytes]) -> ParseStep ParseError r)
-> State# ParserState
-> Result ParseError r
forall e r e r.
[Bytes]
-> Result e r
-> (State# ParserState
-> (Result e r, [Bytes]) -> Bytes -> Result e r)
-> State# ParserState
-> Result e r
go [Bytes
inp] Result ParseError a
r0 State# ParserState
-> (Result ParseError a, [Bytes]) -> ParseStep ParseError r
k0 State# ParserState
st0
match :: Parser a -> Parser (V.Bytes, a)
{-# INLINE match #-}
match :: Parser a -> Parser (Bytes, a)
match Parser a
p = do
(Result ParseError a
r, [Bytes]
bss) <- Parser a -> Parser (Result ParseError a, [Bytes])
forall a. Parser a -> Parser (Result ParseError a, [Bytes])
runAndKeepTrack Parser a
p
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> (Bytes, a) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Bytes, a)
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> (Bytes, a) -> ParseStep ParseError r
k State# ParserState
s Bytes
_ ->
case Result ParseError a
r of
Success a
r' Bytes
inp' -> let !consumed :: Bytes
consumed = Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.dropR (Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
inp') ([Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
bss))
in State# ParserState -> (Bytes, a) -> ParseStep ParseError r
k State# ParserState
s (Bytes
consumed , a
r') Bytes
inp'
Failure ParseError
err Bytes
inp' -> ParseError -> ParseStep ParseError r
forall e r. e -> Bytes -> Result e r
Failure ParseError
err Bytes
inp'
Partial ParseStep ParseError a
_ -> String -> Result ParseError r
forall a. HasCallStack => String -> a
error String
"Z.Data.Parser.Base.match: impossible")
ensureN :: Int -> T.Text -> Parser ()
{-# INLINE ensureN #-}
ensureN :: Int -> Text -> Parser ()
ensureN Int
n0 Text
err = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ())
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> do
let l :: Int
l = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
inp
if Int
n0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
l
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () Bytes
inp
else ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (Text
-> Int
-> Bytes
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
Text
-> Int
-> Bytes
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
ensureNPartial Text
err (Int
n0Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l) Bytes
inp ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s)
where
ensureNPartial :: forall r. T.Text -> Int -> V.PrimVector Word8 -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState -> ParseStep ParseError r
{-# INLINE ensureNPartial #-}
ensureNPartial :: Text
-> Int
-> Bytes
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
ensureNPartial Text
err !Int
l0 Bytes
inp0 ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s0 =
let go :: [Bytes] -> Int -> State# ParserState -> ParseStep ParseError r
go [Bytes]
acc !Int
l State# ParserState
s = \ Bytes
inp -> do
let l' :: Int
l' = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
inp
if Int
l' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then ParseError -> ParseStep ParseError r
kf [Text
err] ([Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse (Bytes
inpBytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
:[Bytes]
acc)))
else do
if Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
l'
then let !inp' :: Bytes
inp' = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse (Bytes
inpBytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
:[Bytes]
acc)) in State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () Bytes
inp'
else ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ([Bytes] -> Int -> State# ParserState -> ParseStep ParseError r
go (Bytes
inpBytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
:[Bytes]
acc) (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l') State# ParserState
s)
in [Bytes] -> Int -> State# ParserState -> ParseStep ParseError r
go [Bytes
inp0] Int
l0 State# ParserState
s0
currentChunk :: Parser V.Bytes
{-# INLINE currentChunk #-}
currentChunk :: Parser Bytes
currentChunk = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes)
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
_ State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (\ Bytes
inp' -> State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp' Bytes
forall (v :: * -> *) a. Vec v a => v a
V.empty)
else State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp Bytes
forall (v :: * -> *) a. Vec v a => v a
V.empty
endOfInput :: Parser ()
{-# INLINE endOfInput #-}
endOfInput :: Parser ()
endOfInput = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ())
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (\ Bytes
inp' ->
if (Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp')
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () Bytes
inp'
else ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.endOfInput: end not reached yet"] Bytes
inp')
else ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.endOfInput: end not reached yet"] Bytes
inp
atEnd :: Parser Bool
{-# INLINE atEnd #-}
atEnd :: Parser Bool
atEnd = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bool -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bool
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bool -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bool)
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bool -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bool
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
_ State# ParserState -> Bool -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (\ Bytes
inp' -> State# ParserState -> Bool -> ParseStep ParseError r
k State# ParserState
s (Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp') Bytes
inp')
else State# ParserState -> Bool -> ParseStep ParseError r
k State# ParserState
s Bool
False Bytes
inp
decodePrim :: forall a. (Unaligned a) => Parser a
{-# INLINE decodePrim #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Word #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Word64 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Word32 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Word16 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Word8 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Int #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Int64 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Int32 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Int16 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Int8 #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Double #-}
{-# SPECIALIZE INLINE decodePrim :: Parser Float #-}
decodePrim :: Parser a
decodePrim = do
Int -> Text -> Parser ()
ensureN Int
n Text
"Z.Data.Parser.Base.decodePrim: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s (V.PrimVector PrimArray Word8
ba Int
i Int
len) ->
let !r :: a
r = PrimArray Word8 -> Int -> a
forall a. Unaligned a => PrimArray Word8 -> Int -> a
indexPrimWord8ArrayAs PrimArray Word8
ba Int
i
in State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s a
r (PrimArray Word8 -> Int -> Int -> Bytes
forall a. PrimArray a -> Int -> Int -> PrimVector a
V.PrimVector PrimArray Word8
ba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n)))
where
n :: Int
n = UnalignedSize a -> Int
forall k (a :: k). UnalignedSize a -> Int
getUnalignedSize (Unaligned a => UnalignedSize a
forall a. Unaligned a => UnalignedSize a
unalignedSize @a)
#define DECODE_HOST(f, type) \
f :: Parser type; {-# INLINE f #-}; f = decodePrim; \
-- ^ Decode type in host endian order.
DECODE_HOST(decodeWord , Word )
DECODE_HOST(decodeWord64, Word64 )
DECODE_HOST(decodeWord32, Word32 )
DECODE_HOST(decodeWord16, Word16 )
DECODE_HOST(decodeWord8 , Word8 )
DECODE_HOST(decodeInt , Int )
DECODE_HOST(decodeInt64 , Int64 )
DECODE_HOST(decodeInt32 , Int32 )
DECODE_HOST(decodeInt16 , Int16 )
DECODE_HOST(decodeInt8 , Int8 )
DECODE_HOST(decodeDouble, Double )
DECODE_HOST(decodeFloat , Float )
decodePrimLE :: forall a. (Unaligned (LE a)) => Parser a
{-# INLINE decodePrimLE #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Word #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Word64 #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Word32 #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Word16 #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Int #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Int64 #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Int32 #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Int16 #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Double #-}
{-# SPECIALIZE INLINE decodePrimLE :: Parser Float #-}
decodePrimLE :: Parser a
decodePrimLE = do
Int -> Text -> Parser ()
ensureN Int
n Text
"Z.Data.Parser.Base.decodePrimLE: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s (V.PrimVector PrimArray Word8
ba Int
i Int
len) ->
let !r :: LE a
r = PrimArray Word8 -> Int -> LE a
forall a. Unaligned a => PrimArray Word8 -> Int -> a
indexPrimWord8ArrayAs PrimArray Word8
ba Int
i
in State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s (LE a -> a
forall a. LE a -> a
getLE LE a
r) (PrimArray Word8 -> Int -> Int -> Bytes
forall a. PrimArray a -> Int -> Int -> PrimVector a
V.PrimVector PrimArray Word8
ba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n)))
where
n :: Int
n = UnalignedSize (LE a) -> Int
forall k (a :: k). UnalignedSize a -> Int
getUnalignedSize (Unaligned (LE a) => UnalignedSize (LE a)
forall a. Unaligned a => UnalignedSize a
unalignedSize @(LE a))
#define DECODE_LE(f, type) \
f :: Parser type; {-# INLINE f #-}; f = decodePrimLE; \
-- ^ Decode type in little endian order.
DECODE_LE(decodeWordLE , Word )
DECODE_LE(decodeWord64LE, Word64 )
DECODE_LE(decodeWord32LE, Word32 )
DECODE_LE(decodeWord16LE, Word16 )
DECODE_LE(decodeIntLE , Int )
DECODE_LE(decodeInt64LE , Int64 )
DECODE_LE(decodeInt32LE , Int32 )
DECODE_LE(decodeInt16LE , Int16 )
DECODE_LE(decodeDoubleLE, Double )
DECODE_LE(decodeFloatLE , Float )
decodePrimBE :: forall a. (Unaligned (BE a)) => Parser a
{-# INLINE decodePrimBE #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Word #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Word64 #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Word32 #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Word16 #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Int #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Int64 #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Int32 #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Int16 #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Double #-}
{-# SPECIALIZE INLINE decodePrimBE :: Parser Float #-}
decodePrimBE :: Parser a
decodePrimBE = do
Int -> Text -> Parser ()
ensureN Int
n Text
"Z.Data.Parser.Base.decodePrimBE: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s (V.PrimVector PrimArray Word8
ba Int
i Int
len) ->
let !r :: BE a
r = PrimArray Word8 -> Int -> BE a
forall a. Unaligned a => PrimArray Word8 -> Int -> a
indexPrimWord8ArrayAs PrimArray Word8
ba Int
i
in State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s (BE a -> a
forall a. BE a -> a
getBE BE a
r) (PrimArray Word8 -> Int -> Int -> Bytes
forall a. PrimArray a -> Int -> Int -> PrimVector a
V.PrimVector PrimArray Word8
ba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n)))
where
n :: Int
n = UnalignedSize (BE a) -> Int
forall k (a :: k). UnalignedSize a -> Int
getUnalignedSize (Unaligned (BE a) => UnalignedSize (BE a)
forall a. Unaligned a => UnalignedSize a
unalignedSize @(BE a))
#define DECODE_BE(f, type) \
f :: Parser type; {-# INLINE f #-}; f = decodePrimBE; \
-- ^ Decode type in big endian order.
DECODE_BE(decodeWordBE , Word )
DECODE_BE(decodeWord64BE, Word64 )
DECODE_BE(decodeWord32BE, Word32 )
DECODE_BE(decodeWord16BE, Word16 )
DECODE_BE(decodeIntBE , Int )
DECODE_BE(decodeInt64BE , Int64 )
DECODE_BE(decodeInt32BE , Int32 )
DECODE_BE(decodeInt16BE , Int16 )
DECODE_BE(decodeDoubleBE, Double )
DECODE_BE(decodeFloatBE , Float )
scan :: s -> (s -> Word8 -> Maybe s) -> Parser (V.Bytes, s)
{-# INLINE scan #-}
scan :: s -> (s -> Word8 -> Maybe s) -> Parser (Bytes, s)
scan s
s0 s -> Word8 -> Maybe s
f = s
-> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s)
forall s.
s
-> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s)
scanChunks s
s0 s -> Bytes -> Either s (Bytes, Bytes, s)
f'
where
f' :: s -> Bytes -> Either s (Bytes, Bytes, s)
f' s
s0' (V.PrimVector PrimArray Word8
arr Int
off Int
l) =
let !end :: Int
end = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l
go :: s -> Int -> Either s (Bytes, Bytes, s)
go !s
st !Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
end = do
let !w :: Word8
w = PrimArray Word8 -> Int -> Word8
forall a. Prim a => PrimArray a -> Int -> a
A.indexPrimArray PrimArray Word8
arr Int
i
case s -> Word8 -> Maybe s
f s
st Word8
w of
Just s
st' -> s -> Int -> Either s (Bytes, Bytes, s)
go s
st' (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
Maybe s
_ ->
let !len1 :: Int
len1 = Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
off
!len2 :: Int
len2 = Int
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
off
in (Bytes, Bytes, s) -> Either s (Bytes, Bytes, s)
forall a b. b -> Either a b
Right (PrimArray Word8 -> Int -> Int -> Bytes
forall a. PrimArray a -> Int -> Int -> PrimVector a
V.PrimVector PrimArray Word8
arr Int
off Int
len1, PrimArray Word8 -> Int -> Int -> Bytes
forall a. PrimArray a -> Int -> Int -> PrimVector a
V.PrimVector PrimArray Word8
arr Int
i Int
len2, s
st)
| Bool
otherwise = s -> Either s (Bytes, Bytes, s)
forall a b. a -> Either a b
Left s
st
in s -> Int -> Either s (Bytes, Bytes, s)
go s
s0' Int
off
scanChunks :: forall s. s -> (s -> V.Bytes -> Either s (V.Bytes, V.Bytes, s)) -> Parser (V.Bytes, s)
{-# INLINE scanChunks #-}
scanChunks :: s
-> (s -> Bytes -> Either s (Bytes, Bytes, s)) -> Parser (Bytes, s)
scanChunks s
s0 s -> Bytes -> Either s (Bytes, Bytes, s)
consume = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> (Bytes, s) -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Bytes, s)
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> (Bytes, s) -> ParseStep ParseError r
k State# ParserState
st Bytes
inp ->
case s -> Bytes -> Either s (Bytes, Bytes, s)
consume s
s0 Bytes
inp of
Right (Bytes
want, Bytes
rest, s
s') -> State# ParserState -> (Bytes, s) -> ParseStep ParseError r
k State# ParserState
st (Bytes
want, s
s') Bytes
rest
Left s
s' -> ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (s
-> (State# ParserState -> (Bytes, s) -> ParseStep ParseError r)
-> State# ParserState
-> Bytes
-> ParseStep ParseError r
forall r.
s
-> (State# ParserState -> (Bytes, s) -> ParseStep ParseError r)
-> State# ParserState
-> Bytes
-> ParseStep ParseError r
scanChunksPartial s
s' State# ParserState -> (Bytes, s) -> ParseStep ParseError r
k State# ParserState
st Bytes
inp))
where
{-# INLINABLE scanChunksPartial #-}
scanChunksPartial :: forall r. s -> (State# ParserState -> (V.PrimVector Word8, s) -> ParseStep ParseError r)
-> State# ParserState -> V.PrimVector Word8 -> ParseStep ParseError r
scanChunksPartial :: s
-> (State# ParserState -> (Bytes, s) -> ParseStep ParseError r)
-> State# ParserState
-> Bytes
-> ParseStep ParseError r
scanChunksPartial s
s0' State# ParserState -> (Bytes, s) -> ParseStep ParseError r
k State# ParserState
st0 Bytes
inp0 =
let go :: s -> [Bytes] -> State# ParserState -> ParseStep ParseError r
go s
s [Bytes]
acc State# ParserState
st = \ Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then State# ParserState -> (Bytes, s) -> ParseStep ParseError r
k State# ParserState
st ([Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc), s
s) Bytes
inp
else case s -> Bytes -> Either s (Bytes, Bytes, s)
consume s
s Bytes
inp of
Left s
s' -> do
let acc' :: [Bytes]
acc' = Bytes
inp Bytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
: [Bytes]
acc
ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (s -> [Bytes] -> State# ParserState -> ParseStep ParseError r
go s
s' [Bytes]
acc' State# ParserState
st)
Right (Bytes
want,Bytes
rest,s
s') ->
let !r :: Bytes
r = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse (Bytes
wantBytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
:[Bytes]
acc)) in State# ParserState -> (Bytes, s) -> ParseStep ParseError r
k State# ParserState
st (Bytes
r, s
s') Bytes
rest
in s -> [Bytes] -> State# ParserState -> ParseStep ParseError r
go s
s0' [Bytes
inp0] State# ParserState
st0
peekMaybe :: Parser (Maybe Word8)
{-# INLINE peekMaybe #-}
peekMaybe :: Parser (Maybe Word8)
peekMaybe =
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Maybe Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Maybe Word8)
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Maybe Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Maybe Word8))
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Maybe Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Maybe Word8)
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
_ State# ParserState -> Maybe Word8 -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (\ Bytes
inp' -> State# ParserState -> Maybe Word8 -> ParseStep ParseError r
k State# ParserState
s (if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp'
then Maybe Word8
forall k1. Maybe k1
Nothing
else Word8 -> Maybe Word8
forall k1. k1 -> Maybe k1
Just (Bytes -> Word8
forall (v :: * -> *) a. Vec v a => v a -> a
V.unsafeHead Bytes
inp')) Bytes
inp')
else State# ParserState -> Maybe Word8 -> ParseStep ParseError r
k State# ParserState
s (Word8 -> Maybe Word8
forall k1. k1 -> Maybe k1
Just (Bytes -> Word8
forall (v :: * -> *) a. Vec v a => v a -> a
V.unsafeHead Bytes
inp)) Bytes
inp
peek :: Parser Word8
{-# INLINE peek #-}
peek :: Parser Word8
peek =
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Word8
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Word8)
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Word8
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
kf State# ParserState -> Word8 -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (\ Bytes
inp' ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp'
then ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.peek: not enough bytes"] Bytes
inp'
else State# ParserState -> Word8 -> ParseStep ParseError r
k State# ParserState
s (Bytes -> Word8
forall (v :: * -> *) a. Vec v a => v a -> a
V.unsafeHead Bytes
inp') Bytes
inp')
else State# ParserState -> Word8 -> ParseStep ParseError r
k State# ParserState
s (Bytes -> Word8
forall (v :: * -> *) a. Vec v a => v a -> a
V.unsafeHead Bytes
inp) Bytes
inp
satisfy :: (Word8 -> Bool) -> Parser Word8
{-# INLINE satisfy #-}
satisfy :: (Word8 -> Bool) -> Parser Word8
satisfy Word8 -> Bool
p = do
Int -> Text -> Parser ()
ensureN Int
1 Text
"Z.Data.Parser.Base.satisfy: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Word8
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Word8)
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Word8 -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Word8
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
kf State# ParserState -> Word8 -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let w :: Word8
w = Bytes -> Word8
forall (v :: * -> *) a. Vec v a => v a -> a
V.unsafeHead Bytes
inp
in if Word8 -> Bool
p Word8
w
then State# ParserState -> Word8 -> ParseStep ParseError r
k State# ParserState
s Word8
w (Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => v a -> v a
V.unsafeTail Bytes
inp)
else ParseError -> ParseStep ParseError r
kf [ Text
"Z.Data.Parser.Base.satisfy: unsatisfied bytes " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Bytes -> Text
forall a. Print a => a -> Text
T.toText (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.take Int
8 Bytes
inp) ]
(Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => v a -> v a
V.unsafeTail Bytes
inp)
satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
{-# INLINE satisfyWith #-}
satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
satisfyWith Word8 -> a
f a -> Bool
p = do
Int -> Text -> Parser ()
ensureN Int
1 Text
"Z.Data.Parser.Base.satisfyWith: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a)
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
kf State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let a :: a
a = Word8 -> a
f (Bytes -> Word8
forall (v :: * -> *) a. Vec v a => v a -> a
V.unsafeHead Bytes
inp)
in if a -> Bool
p a
a
then State# ParserState -> a -> ParseStep ParseError r
k State# ParserState
s a
a (Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => v a -> v a
V.unsafeTail Bytes
inp)
else ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.satisfyWith: unsatisfied byte"] (Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => v a -> v a
V.unsafeTail Bytes
inp)
word8 :: Word8 -> Parser ()
{-# INLINE word8 #-}
word8 :: Word8 -> Parser ()
word8 Word8
w' = do
Int -> Text -> Parser ()
ensureN Int
1 Text
"Z.Data.Parser.Base.word8: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let w :: Word8
w = Bytes -> Word8
forall (v :: * -> *) a. Vec v a => v a -> a
V.unsafeHead Bytes
inp
in if Word8
w Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w'
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () (Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => v a -> v a
V.unsafeTail Bytes
inp)
else ParseError -> ParseStep ParseError r
kf [ ParseError -> Text
T.concat [
Text
"Z.Data.Parser.Base.word8: mismatch byte, expected "
, Word8 -> Text
forall a. Print a => a -> Text
T.toText Word8
w'
, Text
", meet "
, Word8 -> Text
forall a. Print a => a -> Text
T.toText Word8
w
, Text
" at "
, Bytes -> Text
forall a. Print a => a -> Text
T.toText (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.take Int
8 Bytes
inp)
] ] Bytes
inp)
anyWord8 :: Parser Word8
{-# INLINE anyWord8 #-}
anyWord8 :: Parser Word8
anyWord8 = Parser Word8
forall a. Unaligned a => Parser a
decodePrim
char8 :: Char -> Parser ()
{-# INLINE char8 #-}
char8 :: Char -> Parser ()
char8 = Word8 -> Parser ()
word8 (Word8 -> Parser ()) -> (Char -> Word8) -> Char -> Parser ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Word8
c2w
char7 :: Char -> Parser ()
{-# INLINE char7 #-}
char7 :: Char -> Parser ()
char7 Char
chr = Word8 -> Parser ()
word8 (Char -> Word8
c2w Char
chr Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x7F)
charUTF8 :: Char -> Parser ()
{-# INLINE charUTF8 #-}
charUTF8 :: Char -> Parser ()
charUTF8 = Text -> Parser ()
text (Text -> Parser ()) -> (Char -> Text) -> Char -> Parser ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton
anyChar8 :: Parser Char
{-# INLINE anyChar8 #-}
anyChar8 :: Parser Char
anyChar8 = do
Word8
w <- Parser Word8
anyWord8
Char -> Parser Char
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> Parser Char) -> Char -> Parser Char
forall a b. (a -> b) -> a -> b
$! Word8 -> Char
w2c Word8
w
anyChar7 :: Parser Char
{-# INLINE anyChar7 #-}
anyChar7 :: Parser Char
anyChar7 = do
Word8
w <- (Word8 -> Bool) -> Parser Word8
satisfy (Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
0x7f)
Char -> Parser Char
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> Parser Char) -> Char -> Parser Char
forall a b. (a -> b) -> a -> b
$! Word8 -> Char
w2c Word8
w
anyCharUTF8 :: Parser Char
{-# INLINABLE anyCharUTF8 #-}
anyCharUTF8 :: Parser Char
anyCharUTF8 = do
Either Int Char
r <- (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState
-> Either Int Char -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Either Int Char)
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState
-> Either Int Char -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Either Int Char))
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState
-> Either Int Char -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser (Either Int Char)
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
kf State# ParserState -> Either Int Char -> ParseStep ParseError r
k State# ParserState
st inp :: Bytes
inp@(V.PrimVector PrimArray Word8
arr Int
s Int
l) -> do
if Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then
let l' :: Int
l' = PrimArray Word8 -> Int -> Int
T.decodeCharLen PrimArray Word8
arr Int
s
in if Int
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
l
then State# ParserState -> Either Int Char -> ParseStep ParseError r
k State# ParserState
st (Int -> Either Int Char
forall a b. a -> Either a b
Left Int
l') Bytes
inp
else do
case Bytes -> Maybe Text
T.validateMaybe (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeTake Int
l' Bytes
inp) of
Just Text
t -> State# ParserState -> Either Int Char -> ParseStep ParseError r
k State# ParserState
st (Char -> Either Int Char
forall a b. b -> Either a b
Right (Char -> Either Int Char) -> Char -> Either Int Char
forall a b. (a -> b) -> a -> b
$! Text -> Char
T.head Text
t) ParseStep ParseError r -> ParseStep ParseError r
forall a b. (a -> b) -> a -> b
$! Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeDrop Int
l' Bytes
inp
Maybe Text
_ -> ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.anyCharUTF8: invalid UTF8 bytes"] Bytes
inp
else State# ParserState -> Either Int Char -> ParseStep ParseError r
k State# ParserState
st (Int -> Either Int Char
forall a b. a -> Either a b
Left Int
1) Bytes
inp
case Either Int Char
r of
Left Int
d -> do
Int -> Text -> Parser ()
ensureN Int
d Text
"Z.Data.Parser.Base.anyCharUTF8: not enough bytes"
Parser Char
anyCharUTF8
Right Char
c -> Char -> Parser Char
forall (m :: * -> *) a. Monad m => a -> m a
return Char
c
endOfLine :: Parser ()
{-# INLINE endOfLine #-}
endOfLine :: Parser ()
endOfLine = do
Word8
w <- Parser Word8
forall a. Unaligned a => Parser a
decodePrim :: Parser Word8
case Word8
w of
Word8
10 -> () -> Parser ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Word8
13 -> Word8 -> Parser ()
word8 Word8
10
Word8
_ -> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
_ State# ParserState
_ Bytes
inp -> ParseError -> ParseStep ParseError r
kf [
ParseError -> Text
T.concat [
Text
"Z.Data.Parser.Base.endOfLine: mismatch byte, expected 10 or 13, meet "
, Word8 -> Text
forall a. Print a => a -> Text
T.toText Word8
w
, Text
" at "
, Bytes -> Text
forall a. Print a => a -> Text
T.toText (Word8 -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => a -> v a -> v a
V.cons Word8
w (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.take Int
8 Bytes
inp))
] ] Bytes
inp)
skip :: Int -> Parser ()
{-# INLINE skip #-}
skip :: Int -> Parser ()
skip Int
n =
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let l :: Int
l = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
inp
!n' :: Int
n' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
n Int
0
in if Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n'
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () ParseStep ParseError r -> ParseStep ParseError r
forall a b. (a -> b) -> a -> b
$! Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeDrop Int
n' Bytes
inp
else ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (Int
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
forall r.
Int
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
skipPartial (Int
n'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l) ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s))
skipPartial :: Int -> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState -> ParseStep ParseError r
{-# INLINABLE skipPartial #-}
skipPartial :: Int
-> (ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r
skipPartial Int
n ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s0 =
let go :: Int -> State# ParserState -> ParseStep ParseError r
go !Int
n' State# ParserState
s = \ Bytes
inp ->
let l :: Int
l = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
inp
in if Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n'
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () ParseStep ParseError r -> ParseStep ParseError r
forall a b. (a -> b) -> a -> b
$! Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeDrop Int
n' Bytes
inp
else if Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.skip: not enough bytes"] Bytes
inp
else ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (Int -> State# ParserState -> ParseStep ParseError r
go (Int
n'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
l) State# ParserState
s)
in Int -> State# ParserState -> ParseStep ParseError r
go Int
n State# ParserState
s0
skipWord8 :: Parser ()
{-# INLINE skipWord8 #-}
skipWord8 :: Parser ()
skipWord8 =
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser ((forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ())
-> (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a b. (a -> b) -> a -> b
$ \ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (\ Bytes
inp' ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp'
then ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.skipWord8: not enough bytes"] Bytes
inp'
else State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () (Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => v a -> v a
V.unsafeTail Bytes
inp'))
else State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () (Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => v a -> v a
V.unsafeTail Bytes
inp)
skipWhile :: (Word8 -> Bool) -> Parser ()
{-# INLINE skipWhile #-}
skipWhile :: (Word8 -> Bool) -> Parser ()
skipWhile Word8 -> Bool
p =
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let rest :: Bytes
rest = (Word8 -> Bool) -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => (a -> Bool) -> v a -> v a
V.dropWhile Word8 -> Bool
p Bytes
inp
in if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
rest
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ((State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState -> ParseStep ParseError r
forall r.
(State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState -> ParseStep ParseError r
skipWhilePartial State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s)
else State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () Bytes
rest)
where
{-# INLINABLE skipWhilePartial #-}
skipWhilePartial :: forall r. (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState -> ParseStep ParseError r
skipWhilePartial :: (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState -> ParseStep ParseError r
skipWhilePartial State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s0 =
let go :: State# ParserState -> ParseStep ParseError r
go State# ParserState
s = \ Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () Bytes
inp
else
let !rest :: Bytes
rest = (Word8 -> Bool) -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => (a -> Bool) -> v a -> v a
V.dropWhile Word8 -> Bool
p Bytes
inp
in if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
rest then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial (State# ParserState -> ParseStep ParseError r
go State# ParserState
s) else State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () Bytes
rest
in State# ParserState -> ParseStep ParseError r
go State# ParserState
s0
skipSpaces :: Parser ()
{-# INLINE skipSpaces #-}
skipSpaces :: Parser ()
skipSpaces = (Word8 -> Bool) -> Parser ()
skipWhile Word8 -> Bool
isSpace
take :: Int -> Parser V.Bytes
{-# INLINE take #-}
take :: Int -> Parser Bytes
take Int
n = do
Int -> Text -> Parser ()
ensureN Int
n' Text
"Z.Data.Parser.Base.take: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let !r :: Bytes
r = Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeTake Int
n' Bytes
inp
!inp' :: Bytes
inp' = Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeDrop Int
n' Bytes
inp
in State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
r Bytes
inp')
where !n' :: Int
n' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 Int
n
takeTill :: (Word8 -> Bool) -> Parser V.Bytes
{-# INLINE takeTill #-}
takeTill :: (Word8 -> Bool) -> Parser Bytes
takeTill Word8 -> Bool
p = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let (Bytes
want, Bytes
rest) = (Word8 -> Bool) -> Bytes -> (Bytes, Bytes)
forall (v :: * -> *) a. Vec v a => (a -> Bool) -> v a -> (v a, v a)
V.break Word8 -> Bool
p Bytes
inp
in if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
rest
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ((State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
forall r.
(State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
takeTillPartial State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
want)
else State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
want Bytes
rest)
where
{-# INLINABLE takeTillPartial #-}
takeTillPartial :: forall r. (State# ParserState -> V.PrimVector Word8 -> ParseStep ParseError r)
-> State# ParserState -> V.PrimVector Word8 -> ParseStep ParseError r
takeTillPartial :: (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
takeTillPartial State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s0 Bytes
want =
let go :: [Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes]
acc State# ParserState
s = \ Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then let !r :: Bytes
r = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc) in State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
r Bytes
inp
else
let (Bytes
want', Bytes
rest) = (Word8 -> Bool) -> Bytes -> (Bytes, Bytes)
forall (v :: * -> *) a. Vec v a => (a -> Bool) -> v a -> (v a, v a)
V.break Word8 -> Bool
p Bytes
inp
acc' :: [Bytes]
acc' = Bytes
want' Bytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
: [Bytes]
acc
in if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
rest
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ([Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes]
acc' State# ParserState
s)
else let !r :: Bytes
r = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc') in State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
r Bytes
rest
in [Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes
want] State# ParserState
s0
takeWhile :: (Word8 -> Bool) -> Parser V.Bytes
{-# INLINE takeWhile #-}
takeWhile :: (Word8 -> Bool) -> Parser Bytes
takeWhile Word8 -> Bool
p = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
let (Bytes
want, Bytes
rest) = (Word8 -> Bool) -> Bytes -> (Bytes, Bytes)
forall (v :: * -> *) a. Vec v a => (a -> Bool) -> v a -> (v a, v a)
V.span Word8 -> Bool
p Bytes
inp
in if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
rest
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ((State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
forall r.
(State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
takeWhilePartial State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
want)
else State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
want Bytes
rest)
where
{-# INLINABLE takeWhilePartial #-}
takeWhilePartial :: forall r. (State# ParserState -> V.PrimVector Word8 -> ParseStep ParseError r)
-> State# ParserState -> V.PrimVector Word8 -> ParseStep ParseError r
takeWhilePartial :: (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
takeWhilePartial State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s0 Bytes
want =
let go :: [Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes]
acc State# ParserState
s = \ Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then let !r :: Bytes
r = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc) in State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
r Bytes
inp
else
let (Bytes
want', Bytes
rest) = (Word8 -> Bool) -> Bytes -> (Bytes, Bytes)
forall (v :: * -> *) a. Vec v a => (a -> Bool) -> v a -> (v a, v a)
V.span Word8 -> Bool
p Bytes
inp
acc' :: [Bytes]
acc' = Bytes
want' Bytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
: [Bytes]
acc
in if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
rest
then ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ([Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes]
acc' State# ParserState
s)
else let !r :: Bytes
r = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc') in State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
r Bytes
rest
in [Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes
want] State# ParserState
s0
takeWhile1 :: (Word8 -> Bool) -> Parser V.Bytes
{-# INLINE takeWhile1 #-}
takeWhile1 :: (Word8 -> Bool) -> Parser Bytes
takeWhile1 Word8 -> Bool
p = do
Bytes
bs <- (Word8 -> Bool) -> Parser Bytes
takeWhile Word8 -> Bool
p
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
bs
then (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> Bytes -> ParseStep ParseError r
_ State# ParserState
_ Bytes
inp ->
ParseError -> ParseStep ParseError r
kf [Text
"Z.Data.Parser.Base.takeWhile1: no satisfied byte at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Bytes -> Text
forall a. Print a => a -> Text
T.toText (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.take Int
10 Bytes
inp) ]
Bytes
inp)
else Bytes -> Parser Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
bs
takeRemaining :: Parser V.Bytes
{-# INLINE takeRemaining #-}
takeRemaining :: Parser Bytes
takeRemaining = (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
_ State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp -> ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ((State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
forall r.
(State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
takeRemainingPartial State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
inp))
where
{-# INLINABLE takeRemainingPartial #-}
takeRemainingPartial :: forall r. (State# ParserState -> V.PrimVector Word8 -> ParseStep ParseError r)
-> State# ParserState -> V.PrimVector Word8 -> ParseStep ParseError r
takeRemainingPartial :: (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState -> Bytes -> ParseStep ParseError r
takeRemainingPartial State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s0 Bytes
want =
let go :: [Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes]
acc State# ParserState
s = \ Bytes
inp ->
if Bytes -> Bool
forall (v :: * -> *) a. Vec v a => v a -> Bool
V.null Bytes
inp
then let !r :: Bytes
r = [Bytes] -> Bytes
forall (v :: * -> *) a. Vec v a => [v a] -> v a
V.concat ([Bytes] -> [Bytes]
forall a. [a] -> [a]
reverse [Bytes]
acc) in State# ParserState -> Bytes -> ParseStep ParseError r
k State# ParserState
s Bytes
r Bytes
inp
else let acc' :: [Bytes]
acc' = Bytes
inp Bytes -> [Bytes] -> [Bytes]
forall k1. k1 -> [k1] -> [k1]
: [Bytes]
acc in ParseStep ParseError r -> Result ParseError r
forall e r. (Bytes -> Result e r) -> Result e r
Partial ([Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes]
acc' State# ParserState
s)
in [Bytes] -> State# ParserState -> ParseStep ParseError r
go [Bytes
want] State# ParserState
s0
takeN :: (Word8 -> Bool) -> Int -> Parser V.Bytes
{-# INLINE takeN #-}
takeN :: (Word8 -> Bool) -> Int -> Parser Bytes
takeN Word8 -> Bool
p Int
n = do
Bytes
bs <- Int -> Parser Bytes
take Int
n
if Bytes -> Int -> Bool
go Bytes
bs Int
0
then Bytes -> Parser Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
bs
else (forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> Bytes -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser Bytes
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> Bytes -> ParseStep ParseError r
_ State# ParserState
_ Bytes
inp ->
ParseError -> ParseStep ParseError r
kf [ Text
"Z.Data.Parser.Base.takeN: byte does not satisfy at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Bytes -> Text
forall a. Print a => a -> Text
T.toText (Bytes
bs Bytes -> Bytes -> Bytes
forall a. Semigroup a => a -> a -> a
<> Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.take Int
10 Bytes
inp) ]
Bytes
inp)
where
go :: Bytes -> Int -> Bool
go bs :: Bytes
bs@(V.PrimVector PrimArray Word8
_ Int
_ Int
l) !Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
l = Word8 -> Bool
p (Bytes -> Int -> Word8
forall (v :: * -> *) a. Vec v a => v a -> Int -> a
V.unsafeIndex Bytes
bs Int
i) Bool -> Bool -> Bool
&& Bytes -> Int -> Bool
go Bytes
bs (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
| Bool
otherwise = Bool
True
bytes :: V.Bytes -> Parser ()
{-# INLINE bytes #-}
bytes :: Bytes -> Parser ()
bytes Bytes
bs = do
let n :: Int
n = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
bs
Int -> Text -> Parser ()
ensureN Int
n Text
"Z.Data.Parser.Base.bytes: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes
bs Bytes -> Bytes -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeTake Int
n Bytes
inp
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () ParseStep ParseError r -> ParseStep ParseError r
forall a b. (a -> b) -> a -> b
$! Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeDrop Int
n Bytes
inp
else ParseError -> ParseStep ParseError r
kf [ ParseError -> Text
T.concat [
Text
"Z.Data.Parser.Base.bytes: mismatch bytes, expected "
, Bytes -> Text
forall a. Print a => a -> Text
T.toText Bytes
bs
, Text
", meet "
, Bytes -> Text
forall a. Print a => a -> Text
T.toText (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.take Int
n Bytes
inp)
] ] Bytes
inp)
bytesCI :: V.Bytes -> Parser ()
{-# INLINE bytesCI #-}
bytesCI :: Bytes -> Parser ()
bytesCI Bytes
bs = do
let n :: Int
n = Bytes -> Int
forall (v :: * -> *) a. Vec v a => v a -> Int
V.length Bytes
bs
Int -> Text -> Parser ()
ensureN Int
n Text
"Z.Data.Parser.Base.bytesCI: not enough bytes"
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> () -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser ()
forall a.
(forall r.
(ParseError -> ParseStep ParseError r)
-> (State# ParserState -> a -> ParseStep ParseError r)
-> State# ParserState
-> ParseStep ParseError r)
-> Parser a
Parser (\ ParseError -> ParseStep ParseError r
kf State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s Bytes
inp ->
if Bytes
bs' Bytes -> Bytes -> Bool
forall a. Eq a => a -> a -> Bool
== Bytes -> Bytes
forall s. FoldCase s => s -> s
CI.foldCase (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeTake Int
n Bytes
inp)
then State# ParserState -> () -> ParseStep ParseError r
k State# ParserState
s () ParseStep ParseError r -> ParseStep ParseError r
forall a b. (a -> b) -> a -> b
$! Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.unsafeDrop Int
n Bytes
inp
else ParseError -> ParseStep ParseError r
kf [ ParseError -> Text
T.concat [
Text
"Z.Data.Parser.Base.bytesCI: mismatch bytes, expected "
, Bytes -> Text
forall a. Print a => a -> Text
T.toText Bytes
bs
, Text
"(case insensitive), meet "
, Bytes -> Text
forall a. Print a => a -> Text
T.toText (Int -> Bytes -> Bytes
forall (v :: * -> *) a. Vec v a => Int -> v a -> v a
V.take Int
n Bytes
inp)
] ] Bytes
inp)
where
bs' :: Bytes
bs' = Bytes -> Bytes
forall s. FoldCase s => s -> s
CI.foldCase Bytes
bs
text :: T.Text -> Parser ()
{-# INLINE text #-}
text :: Text -> Parser ()
text (T.Text Bytes
bs) = Bytes -> Parser ()
bytes Bytes
bs