{-# language BangPatterns #-}
{-# language BinaryLiterals #-}
{-# language DataKinds #-}
{-# language DeriveFunctor #-}
{-# language DerivingStrategies #-}
{-# language GADTSyntax #-}
{-# language KindSignatures #-}
{-# language LambdaCase #-}
{-# language MagicHash #-}
{-# language MultiWayIf #-}
{-# language PolyKinds #-}
{-# language RankNTypes #-}
{-# language ScopedTypeVariables #-}
{-# language StandaloneDeriving #-}
{-# language TypeApplications #-}
{-# language UnboxedSums #-}
{-# language UnboxedTuples #-}
module Data.Bytes.Parser
(
Parser
, Result(..)
, Slice(..)
, parseByteArray
, parseBytes
, parseBytesEffectfully
, parseBytesEither
, parseBytesMaybe
, any
, take
, takeWhile
, takeTrailedBy
, skipWhile
, skipTrailedBy
, skipTrailedBy2
, skipTrailedBy2#
, skipTrailedBy3#
, byteArray
, bytes
, satisfy
, satisfyWith
, cstring
, endOfInput
, isEndOfInput
, remaining
, peekRemaining
, scan
, peek
, peek'
, fail
, orElse
, annotate
, (<?>)
, replicate
, delimit
, measure
, measure_
, measure_#
, effect
, boxWord32
, boxIntPair
, unboxWord32
, unboxIntPair
, bindFromCharToLifted
, bindFromLiftedToIntPair
, bindFromLiftedToInt
, bindFromIntToIntPair
, bindFromCharToIntPair
, bindFromMaybeCharToIntPair
, bindFromMaybeCharToLifted
, pureIntPair
, failIntPair
) where
import Prelude hiding (length,any,fail,takeWhile,take,replicate)
import Data.Bytes.Parser.Internal (Parser(..),ST#,unboxBytes)
import Data.Bytes.Parser.Internal (boxBytes,Result#,uneffectful,fail)
import Data.Bytes.Parser.Internal (uneffectful#,uneffectfulInt#)
import Data.Bytes.Parser.Types (Result(Failure,Success),Slice(Slice))
import Data.Bytes.Parser.Unsafe (unconsume,expose,cursor)
import Data.Bytes.Types (Bytes(..))
import Data.Primitive (ByteArray(..))
import Foreign.C.String (CString)
import GHC.Exts (Int(I#),Word#,Int#,Char#,runRW#,(+#),(-#),(>=#))
import GHC.ST (ST(..))
import GHC.Word (Word32(W32#),Word8)
import Data.Primitive.Contiguous (Contiguous,Element)
import qualified Data.Bytes as B
import qualified Data.Bytes.Parser.Internal as Internal
import qualified Data.Primitive as PM
import qualified Data.Primitive.Contiguous as C
import qualified GHC.Exts as Exts
parseBytes :: forall e a. (forall s. Parser e s a) -> Bytes -> Result e a
{-# inline parseBytes #-}
parseBytes :: (forall s. Parser e s a) -> Bytes -> Result e a
parseBytes forall s. Parser e s a
p !Bytes
b = (forall s. ST# s (Result# e a)) -> Result e a
forall e x. (forall s. ST# s (Result# e x)) -> Result e x
runResultST forall s. ST# s (Result# e a)
action
where
action :: forall s. ST# s (Result# e a)
action :: ST# s (Result# e a)
action State# s
s0 = case Parser e s a
forall s. Parser e s a
p @s of
Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (Bytes -> (# ByteArray#, Int#, Int# #)
unboxBytes Bytes
b) State# s
s0
parseBytesMaybe :: forall e a. (forall s. Parser e s a) -> Bytes -> Maybe a
{-# inline parseBytesMaybe #-}
parseBytesMaybe :: (forall s. Parser e s a) -> Bytes -> Maybe a
parseBytesMaybe forall s. Parser e s a
p !Bytes
b = (forall s. ST# s (Result# e a)) -> Maybe a
forall e x. (forall s. ST# s (Result# e x)) -> Maybe x
runMaybeST forall s. ST# s (Result# e a)
action
where
action :: forall s. ST# s (Result# e a)
action :: ST# s (Result# e a)
action State# s
s0 = case Parser e s a
forall s. Parser e s a
p @s of
Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (Bytes -> (# ByteArray#, Int#, Int# #)
unboxBytes Bytes
b) State# s
s0
parseBytesEither :: forall e a. (forall s. Parser e s a) -> Bytes -> Either e a
{-# inline parseBytesEither #-}
parseBytesEither :: (forall s. Parser e s a) -> Bytes -> Either e a
parseBytesEither forall s. Parser e s a
p !Bytes
b = (forall s. ST# s (Result# e a)) -> Either e a
forall e x. (forall s. ST# s (Result# e x)) -> Either e x
runEitherST forall s. ST# s (Result# e a)
action
where
action :: forall s. ST# s (Result# e a)
action :: ST# s (Result# e a)
action State# s
s0 = case Parser e s a
forall s. Parser e s a
p @s of
Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (Bytes -> (# ByteArray#, Int#, Int# #)
unboxBytes Bytes
b) State# s
s0
runMaybeST :: (forall s. ST# s (Result# e x)) -> Maybe x
{-# inline runMaybeST #-}
runMaybeST :: (forall s. ST# s (Result# e x)) -> Maybe x
runMaybeST forall s. ST# s (Result# e x)
f = case ((State# RealWorld -> Result# e x) -> Result# e x
forall o. (State# RealWorld -> o) -> o
runRW# (\State# RealWorld
s0 -> case ST# RealWorld (Result# e x)
forall s. ST# s (Result# e x)
f State# RealWorld
s0 of { (# State# RealWorld
_, Result# e x
r #) -> Result# e x
r })) of
(# e
_ | #) -> Maybe x
forall a. Maybe a
Nothing
(# | (# x
x, Int#
_, Int#
_ #) #) -> x -> Maybe x
forall a. a -> Maybe a
Just x
x
runEitherST :: (forall s. ST# s (Result# e x)) -> Either e x
{-# inline runEitherST #-}
runEitherST :: (forall s. ST# s (Result# e x)) -> Either e x
runEitherST forall s. ST# s (Result# e x)
f = case ((State# RealWorld -> Result# e x) -> Result# e x
forall o. (State# RealWorld -> o) -> o
runRW# (\State# RealWorld
s0 -> case ST# RealWorld (Result# e x)
forall s. ST# s (Result# e x)
f State# RealWorld
s0 of { (# State# RealWorld
_, Result# e x
r #) -> Result# e x
r })) of
(# e
e | #) -> e -> Either e x
forall a b. a -> Either a b
Left e
e
(# | (# x
x, Int#
_, Int#
_ #) #) -> x -> Either e x
forall a b. b -> Either a b
Right x
x
runResultST :: (forall s. ST# s (Result# e x)) -> Result e x
{-# inline runResultST #-}
runResultST :: (forall s. ST# s (Result# e x)) -> Result e x
runResultST forall s. ST# s (Result# e x)
f = case ((State# RealWorld -> Result# e x) -> Result# e x
forall o. (State# RealWorld -> o) -> o
runRW# (\State# RealWorld
s0 -> case ST# RealWorld (Result# e x)
forall s. ST# s (Result# e x)
f State# RealWorld
s0 of { (# State# RealWorld
_, Result# e x
r #) -> Result# e x
r })) of
(# e
e | #) -> e -> Result e x
forall e a. e -> Result e a
Failure e
e
(# | (# x
x, Int#
off, Int#
len #) #) -> Slice x -> Result e x
forall e a. Slice a -> Result e a
Success (Int -> Int -> x -> Slice x
forall a. Int -> Int -> a -> Slice a
Slice (Int# -> Int
I# Int#
off) (Int# -> Int
I# Int#
len) x
x)
parseByteArray :: (forall s. Parser e s a) -> ByteArray -> Result e a
{-# inline parseByteArray #-}
parseByteArray :: (forall s. Parser e s a) -> ByteArray -> Result e a
parseByteArray forall s. Parser e s a
p ByteArray
b =
(forall s. Parser e s a) -> Bytes -> Result e a
forall e a. (forall s. Parser e s a) -> Bytes -> Result e a
parseBytes forall s. Parser e s a
p (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
b Int
0 (ByteArray -> Int
PM.sizeofByteArray ByteArray
b))
parseBytesEffectfully :: Parser e s a -> Bytes -> ST s (Result e a)
{-# inline parseBytesEffectfully #-}
parseBytesEffectfully :: Parser e s a -> Bytes -> ST s (Result e a)
parseBytesEffectfully (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) !Bytes
b = STRep s (Result e a) -> ST s (Result e a)
forall s a. STRep s a -> ST s a
ST
(\State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (Bytes -> (# ByteArray#, Int#, Int# #)
unboxBytes Bytes
b) State# s
s0 of
(# State# s
s1, Result# e a
r #) -> (# State# s
s1, Result# e a -> Result e a
forall e a. Result# e a -> Result e a
boxPublicResult Result# e a
r #)
)
effect :: ST s a -> Parser e s a
{-# inline effect #-}
effect :: ST s a -> Parser e s a
effect (ST STRep s a
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
( \(# ByteArray#
_, Int#
off, Int#
len #) State# s
s0 -> case STRep s a
f State# s
s0 of
(# State# s
s1, a
a #) -> (# State# s
s1, (# | (# a
a, Int#
off, Int#
len #) #) #)
)
byteArray :: e -> ByteArray -> Parser e s ()
{-# inline byteArray #-}
byteArray :: e -> ByteArray -> Parser e s ()
byteArray e
e !ByteArray
expected = e -> Bytes -> Parser e s ()
forall e s. e -> Bytes -> Parser e s ()
bytes e
e (ByteArray -> Bytes
B.fromByteArray ByteArray
expected)
bytes :: e -> Bytes -> Parser e s ()
bytes :: e -> Bytes -> Parser e s ()
bytes e
e !Bytes
expected = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e ()))
-> Parser e s ()
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
( \actual :: (# ByteArray#, Int#, Int# #)
actual@(# ByteArray#
_, Int#
off, Int#
len #) State# s
s ->
let r :: Result# e ()
r = if Bytes -> Bytes -> Bool
B.isPrefixOf Bytes
expected ((# ByteArray#, Int#, Int# #) -> Bytes
boxBytes (# ByteArray#, Int#, Int# #)
actual)
then let !(I# Int#
movement) = Bytes -> Int
length Bytes
expected in
(# | (# (), Int#
off Int# -> Int# -> Int#
+# Int#
movement, Int#
len Int# -> Int# -> Int#
-# Int#
movement #) #)
else (# e
e | #)
in (# State# s
s, Result# e ()
r #)
)
cstring :: e -> CString -> Parser e s ()
cstring :: e -> CString -> Parser e s ()
cstring e
e (Exts.Ptr Addr#
ptr0) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e ()))
-> Parser e s ()
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
( \(# ByteArray#
arr, Int#
off0, Int#
len0 #) State# s
s ->
let go :: Addr# -> Int# -> Int# -> (# State# s, Result# e () #)
go !Addr#
ptr !Int#
off !Int#
len = case Addr# -> Int# -> Word#
Exts.indexWord8OffAddr# Addr#
ptr Int#
0# of
Word#
0## -> (# State# s
s, (# | (# (), Int#
off, Int#
len #) #) #)
Word#
c -> case Int#
len of
Int#
0# -> (# State# s
s, (# e
e | #) #)
Int#
_ -> case Word# -> Word# -> Int#
Exts.eqWord# Word#
c (ByteArray# -> Int# -> Word#
Exts.indexWord8Array# ByteArray#
arr Int#
off) of
Int#
1# -> Addr# -> Int# -> Int# -> (# State# s, Result# e () #)
go (Addr# -> Int# -> Addr#
Exts.plusAddr# Addr#
ptr Int#
1# ) (Int#
off Int# -> Int# -> Int#
+# Int#
1# ) (Int#
len Int# -> Int# -> Int#
-# Int#
1# )
Int#
_ -> (# State# s
s, (# e
e | #) #)
in Addr# -> Int# -> Int# -> (# State# s, Result# e () #)
go Addr#
ptr0 Int#
off0 Int#
len0
)
infix 0 <?>
(<?>) :: Parser x s a -> e -> Parser e s a
<?> :: Parser x s a -> e -> Parser e s a
(<?>) = Parser x s a -> e -> Parser e s a
forall x s a e. Parser x s a -> e -> Parser e s a
annotate
annotate :: Parser x s a -> e -> Parser e s a
annotate :: Parser x s a -> e -> Parser e s a
annotate Parser x s a
p e
e = Parser x s a
p Parser x s a -> Parser e s a -> Parser e s a
forall x s a e. Parser x s a -> Parser e s a -> Parser e s a
`orElse` e -> Parser e s a
forall e s a. e -> Parser e s a
fail e
e
any :: e -> Parser e s Word8
{-# inline any #-}
any :: e -> Parser e s Word8
any e
e = (Bytes -> Result e Word8) -> Parser e s Word8
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Word8) -> Parser e s Word8)
-> (Bytes -> Result e Word8) -> Parser e s Word8
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then
let w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) :: Word8
in Word8 -> Int -> Int -> Result e Word8
forall e a. a -> Int -> Int -> Result e a
Internal.Success Word8
w (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
else e -> Result e Word8
forall e a. e -> Result e a
Internal.Failure e
e
peek :: Parser e s (Maybe Word8)
{-# inline peek #-}
peek :: Parser e s (Maybe Word8)
peek = (Bytes -> Result e (Maybe Word8)) -> Parser e s (Maybe Word8)
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e (Maybe Word8)) -> Parser e s (Maybe Word8))
-> (Bytes -> Result e (Maybe Word8)) -> Parser e s (Maybe Word8)
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
let v :: Maybe Word8
v = if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (Bytes -> Int -> Word8
B.unsafeIndex Bytes
chunk Int
0)
else Maybe Word8
forall a. Maybe a
Nothing
in Maybe Word8 -> Int -> Int -> Result e (Maybe Word8)
forall e a. a -> Int -> Int -> Result e a
Internal.Success Maybe Word8
v (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)
peek' :: e -> Parser e s Word8
{-# inline peek' #-}
peek' :: e -> Parser e s Word8
peek' e
e = (Bytes -> Result e Word8) -> Parser e s Word8
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Word8) -> Parser e s Word8)
-> (Bytes -> Result e Word8) -> Parser e s Word8
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then Word8 -> Int -> Int -> Result e Word8
forall e a. a -> Int -> Int -> Result e a
Internal.Success (Bytes -> Int -> Word8
B.unsafeIndex Bytes
chunk Int
0) (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)
else e -> Result e Word8
forall e a. e -> Result e a
Internal.Failure e
e
scan :: state -> (state -> Word8 -> Maybe state) -> Parser e s state
{-# inline scan #-}
scan :: state -> (state -> Word8 -> Maybe state) -> Parser e s state
scan state
s0 state -> Word8 -> Maybe state
t = do
let go :: state -> Parser e s state
go state
s = do
Maybe Word8
mw <- Parser e s (Maybe Word8)
forall e s. Parser e s (Maybe Word8)
peek
case Maybe Word8
mw of
Maybe Word8
Nothing -> state -> Parser e s state
forall (f :: * -> *) a. Applicative f => a -> f a
pure state
s
Just Word8
w -> case state -> Word8 -> Maybe state
t state
s Word8
w of
Just state
s' -> state -> Parser e s state
go state
s'
Maybe state
Nothing -> state -> Parser e s state
forall (f :: * -> *) a. Applicative f => a -> f a
pure state
s
state -> Parser e s state
forall e s. state -> Parser e s state
go state
s0
anyUnsafe :: Parser e s Word8
{-# inline anyUnsafe #-}
anyUnsafe :: Parser e s Word8
anyUnsafe = (Bytes -> Result e Word8) -> Parser e s Word8
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Word8) -> Parser e s Word8)
-> (Bytes -> Result e Word8) -> Parser e s Word8
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
let w :: Word8
w = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
chunk) (Bytes -> Int
offset Bytes
chunk) :: Word8
in Word8 -> Int -> Int -> Result e Word8
forall e a. a -> Int -> Int -> Result e a
Internal.Success Word8
w (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
takeWhile :: (Word8 -> Bool) -> Parser e s Bytes
{-# inline takeWhile #-}
takeWhile :: (Word8 -> Bool) -> Parser e s Bytes
takeWhile Word8 -> Bool
f = (Bytes -> Result e Bytes) -> Parser e s Bytes
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Bytes) -> Parser e s Bytes)
-> (Bytes -> Result e Bytes) -> Parser e s Bytes
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> case (Word8 -> Bool) -> Bytes -> Bytes
B.takeWhile Word8 -> Bool
f Bytes
chunk of
Bytes
bs -> Bytes -> Int -> Int -> Result e Bytes
forall e a. a -> Int -> Int -> Result e a
Internal.Success Bytes
bs (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
bs) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Bytes -> Int
length Bytes
bs)
takeTrailedBy :: e -> Word8 -> Parser e s Bytes
takeTrailedBy :: e -> Word8 -> Parser e s Bytes
takeTrailedBy e
e !Word8
w = do
!Int
start <- Parser e s Int
forall e s. Parser e s Int
cursor
e -> Word8 -> Parser e s ()
forall e s. e -> Word8 -> Parser e s ()
skipTrailedBy e
e Word8
w
!Int
end <- Parser e s Int
forall e s. Parser e s Int
cursor
!ByteArray
arr <- Parser e s ByteArray
forall e s. Parser e s ByteArray
expose
Bytes -> Parser e s Bytes
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteArray -> Int -> Int -> Bytes
Bytes ByteArray
arr Int
start (Int
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)))
skipTrailedBy :: e -> Word8 -> Parser e s ()
{-# inline skipTrailedBy #-}
skipTrailedBy :: e -> Word8 -> Parser e s ()
skipTrailedBy e
e !Word8
w = (Bytes -> Result# e ()) -> Parser e s ()
forall e a s. (Bytes -> Result# e a) -> Parser e s a
uneffectful# (\Bytes
c -> e -> Word8 -> Bytes -> Result# e ()
forall e. e -> Word8 -> Bytes -> Result# e ()
skipUntilConsumeByteLoop e
e Word8
w Bytes
c)
skipUntilConsumeByteLoop ::
e
-> Word8
-> Bytes
-> Result# e ()
skipUntilConsumeByteLoop :: e -> Word8 -> Bytes -> Result# e ()
skipUntilConsumeByteLoop e
e !Word8
w !Bytes
c = if Bytes -> Int
length Bytes
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then if ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c) Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= (Word8
w :: Word8)
then e -> Word8 -> Bytes -> Result# e ()
forall e. e -> Word8 -> Bytes -> Result# e ()
skipUntilConsumeByteLoop e
e Word8
w (Int -> Bytes -> Bytes
B.unsafeDrop Int
1 Bytes
c)
else (# | (# (), Int -> Int#
unI (Bytes -> Int
offset Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1), Int -> Int#
unI (Bytes -> Int
length Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) #) #)
else (# e
e | #)
skipTrailedBy2 ::
e
-> Word8
-> Word8
-> Parser e s Bool
{-# inline skipTrailedBy2 #-}
skipTrailedBy2 :: e -> Word8 -> Word8 -> Parser e s Bool
skipTrailedBy2 e
e !Word8
wa !Word8
wb = Parser e s Int# -> Parser e s Bool
forall e s. Parser e s Int# -> Parser e s Bool
boxBool (e -> Word8 -> Word8 -> Parser e s Int#
forall e s. e -> Word8 -> Word8 -> Parser e s Int#
skipTrailedBy2# e
e Word8
wa Word8
wb)
skipTrailedBy2# ::
e
-> Word8
-> Word8
-> Parser e s Int#
{-# inline skipTrailedBy2# #-}
skipTrailedBy2# :: e -> Word8 -> Word8 -> Parser e s Int#
skipTrailedBy2# e
e !Word8
wa !Word8
wb =
(Bytes -> Result# e Int#) -> Parser e s Int#
forall e s. (Bytes -> Result# e Int#) -> Parser e s Int#
uneffectfulInt# (\Bytes
c -> e -> Word8 -> Word8 -> Bytes -> Result# e Int#
forall e. e -> Word8 -> Word8 -> Bytes -> Result# e Int#
skipUntilConsumeByteEitherLoop e
e Word8
wa Word8
wb Bytes
c)
skipTrailedBy3# ::
e
-> Word8
-> Word8
-> Word8
-> Parser e s Int#
{-# inline skipTrailedBy3# #-}
skipTrailedBy3# :: e -> Word8 -> Word8 -> Word8 -> Parser e s Int#
skipTrailedBy3# e
e !Word8
wa !Word8
wb !Word8
wc =
(Bytes -> Result# e Int#) -> Parser e s Int#
forall e s. (Bytes -> Result# e Int#) -> Parser e s Int#
uneffectfulInt# (\Bytes
c -> e -> Word8 -> Word8 -> Word8 -> Bytes -> Result# e Int#
forall e. e -> Word8 -> Word8 -> Word8 -> Bytes -> Result# e Int#
skipUntilConsumeByte3Loop e
e Word8
wa Word8
wb Word8
wc Bytes
c)
skipUntilConsumeByteEitherLoop ::
e
-> Word8
-> Word8
-> Bytes
-> Result# e Int#
skipUntilConsumeByteEitherLoop :: e -> Word8 -> Word8 -> Bytes -> Result# e Int#
skipUntilConsumeByteEitherLoop e
e !Word8
wa !Word8
wb !Bytes
c = if Bytes -> Int
length Bytes
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then let byte :: Word8
byte = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c) in
if | Word8
byte Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
wa -> (# | (# Int#
0#, Int -> Int#
unI (Bytes -> Int
offset Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1), Int -> Int#
unI (Bytes -> Int
length Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) #) #)
| Word8
byte Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
wb -> (# | (# Int#
1#, Int -> Int#
unI (Bytes -> Int
offset Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1), Int -> Int#
unI (Bytes -> Int
length Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) #) #)
| Bool
otherwise -> e -> Word8 -> Word8 -> Bytes -> Result# e Int#
forall e. e -> Word8 -> Word8 -> Bytes -> Result# e Int#
skipUntilConsumeByteEitherLoop e
e Word8
wa Word8
wb (Int -> Bytes -> Bytes
B.unsafeDrop Int
1 Bytes
c)
else (# e
e | #)
skipUntilConsumeByte3Loop ::
e
-> Word8
-> Word8
-> Word8
-> Bytes
-> Result# e Int#
skipUntilConsumeByte3Loop :: e -> Word8 -> Word8 -> Word8 -> Bytes -> Result# e Int#
skipUntilConsumeByte3Loop e
e !Word8
wa !Word8
wb !Word8
wc !Bytes
c = if Bytes -> Int
length Bytes
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then let byte :: Word8
byte = ByteArray -> Int -> Word8
forall a. Prim a => ByteArray -> Int -> a
PM.indexByteArray (Bytes -> ByteArray
array Bytes
c) (Bytes -> Int
offset Bytes
c) in
if | Word8
byte Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
wa -> (# | (# Int#
0#, Int -> Int#
unI (Bytes -> Int
offset Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1), Int -> Int#
unI (Bytes -> Int
length Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) #) #)
| Word8
byte Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
wb -> (# | (# Int#
1#, Int -> Int#
unI (Bytes -> Int
offset Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1), Int -> Int#
unI (Bytes -> Int
length Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) #) #)
| Word8
byte Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
wc -> (# | (# Int#
2#, Int -> Int#
unI (Bytes -> Int
offset Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1), Int -> Int#
unI (Bytes -> Int
length Bytes
c Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) #) #)
| Bool
otherwise -> e -> Word8 -> Word8 -> Word8 -> Bytes -> Result# e Int#
forall e. e -> Word8 -> Word8 -> Word8 -> Bytes -> Result# e Int#
skipUntilConsumeByte3Loop e
e Word8
wa Word8
wb Word8
wc (Int -> Bytes -> Bytes
B.unsafeDrop Int
1 Bytes
c)
else (# e
e | #)
take :: e -> Int -> Parser e s Bytes
{-# inline take #-}
take :: e -> Int -> Parser e s Bytes
take e
e Int
n = (Bytes -> Result e Bytes) -> Parser e s Bytes
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Bytes) -> Parser e s Bytes)
-> (Bytes -> Result e Bytes) -> Parser e s Bytes
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Bytes -> Int
B.length Bytes
chunk
then case Int -> Bytes -> Bytes
B.unsafeTake Int
n Bytes
chunk of
Bytes
bs -> Bytes -> Int -> Int -> Result e Bytes
forall e a. a -> Int -> Int -> Result e a
Internal.Success Bytes
bs (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
else e -> Result e Bytes
forall e a. e -> Result e a
Internal.Failure e
e
remaining :: Parser e s Bytes
{-# inline remaining #-}
remaining :: Parser e s Bytes
remaining = (Bytes -> Result e Bytes) -> Parser e s Bytes
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Bytes) -> Parser e s Bytes)
-> (Bytes -> Result e Bytes) -> Parser e s Bytes
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
Bytes -> Int -> Int -> Result e Bytes
forall e a. a -> Int -> Int -> Result e a
Internal.Success Bytes
chunk (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Bytes -> Int
length Bytes
chunk) Int
0
peekRemaining :: Parser e s Bytes
{-# inline peekRemaining #-}
peekRemaining :: Parser e s Bytes
peekRemaining = (Bytes -> Result e Bytes) -> Parser e s Bytes
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Bytes) -> Parser e s Bytes)
-> (Bytes -> Result e Bytes) -> Parser e s Bytes
forall a b. (a -> b) -> a -> b
$ \b :: Bytes
b@(Bytes ByteArray
_ Int
off Int
len) ->
Bytes -> Int -> Int -> Result e Bytes
forall e a. a -> Int -> Int -> Result e a
Internal.Success Bytes
b Int
off Int
len
skipWhile :: (Word8 -> Bool) -> Parser e s ()
{-# inline skipWhile #-}
skipWhile :: (Word8 -> Bool) -> Parser e s ()
skipWhile Word8 -> Bool
f = Parser e s ()
forall e s. Parser e s ()
go where
go :: Parser e s ()
go = Parser e s Bool
forall e s. Parser e s Bool
isEndOfInput Parser e s Bool -> (Bool -> Parser e s ()) -> Parser e s ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Bool
True -> () -> Parser e s ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Bool
False -> do
Word8
w <- Parser e s Word8
forall e s. Parser e s Word8
anyUnsafe
if Word8 -> Bool
f Word8
w
then Parser e s ()
go
else Int -> Parser e s ()
forall e s. Int -> Parser e s ()
unconsume Int
1
satisfy :: e -> (Word8 -> Bool) -> Parser e s Word8
satisfy :: e -> (Word8 -> Bool) -> Parser e s Word8
satisfy e
e Word8 -> Bool
p = e -> (Word8 -> Word8) -> (Word8 -> Bool) -> Parser e s Word8
forall e a s. e -> (Word8 -> a) -> (a -> Bool) -> Parser e s a
satisfyWith e
e Word8 -> Word8
forall a. a -> a
id Word8 -> Bool
p
{-# inline satisfy #-}
satisfyWith :: e -> (Word8 -> a) -> (a -> Bool) -> Parser e s a
{-# inline satisfyWith #-}
satisfyWith :: e -> (Word8 -> a) -> (a -> Bool) -> Parser e s a
satisfyWith e
e Word8 -> a
f a -> Bool
p = (Bytes -> Result e a) -> Parser e s a
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e a) -> Parser e s a)
-> (Bytes -> Result e a) -> Parser e s a
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
then case Bytes -> Int -> Word8
B.unsafeIndex Bytes
chunk Int
1 of
Word8
w ->
let v :: a
v = Word8 -> a
f Word8
w
in if a -> Bool
p a
v
then a -> Int -> Int -> Result e a
forall e a. a -> Int -> Int -> Result e a
Internal.Success a
v (Bytes -> Int
offset Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Bytes -> Int
length Bytes
chunk Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
else e -> Result e a
forall e a. e -> Result e a
Internal.Failure e
e
else e -> Result e a
forall e a. e -> Result e a
Internal.Failure e
e
endOfInput :: e -> Parser e s ()
{-# inline endOfInput #-}
endOfInput :: e -> Parser e s ()
endOfInput e
e = (Bytes -> Result e ()) -> Parser e s ()
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e ()) -> Parser e s ())
-> (Bytes -> Result e ()) -> Parser e s ()
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk -> if Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then () -> Int -> Int -> Result e ()
forall e a. a -> Int -> Int -> Result e a
Internal.Success () (Bytes -> Int
offset Bytes
chunk) Int
0
else e -> Result e ()
forall e a. e -> Result e a
Internal.Failure e
e
isEndOfInput :: Parser e s Bool
{-# inline isEndOfInput #-}
isEndOfInput :: Parser e s Bool
isEndOfInput = (Bytes -> Result e Bool) -> Parser e s Bool
forall e a s. (Bytes -> Result e a) -> Parser e s a
uneffectful ((Bytes -> Result e Bool) -> Parser e s Bool)
-> (Bytes -> Result e Bool) -> Parser e s Bool
forall a b. (a -> b) -> a -> b
$ \Bytes
chunk ->
Bool -> Int -> Int -> Result e Bool
forall e a. a -> Int -> Int -> Result e a
Internal.Success (Bytes -> Int
length Bytes
chunk Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Bytes -> Int
offset Bytes
chunk) (Bytes -> Int
length Bytes
chunk)
boxPublicResult :: Result# e a -> Result e a
{-# inline boxPublicResult #-}
boxPublicResult :: Result# e a -> Result e a
boxPublicResult (# | (# a
a, Int#
b, Int#
c #) #) = Slice a -> Result e a
forall e a. Slice a -> Result e a
Success (Int -> Int -> a -> Slice a
forall a. Int -> Int -> a -> Slice a
Slice (Int# -> Int
I# Int#
b) (Int# -> Int
I# Int#
c) a
a)
boxPublicResult (# e
e | #) = e -> Result e a
forall e a. e -> Result e a
Failure e
e
unboxWord32 :: Parser e s Word32 -> Parser e s Word#
{-# inline unboxWord32 #-}
unboxWord32 :: Parser e s Word32 -> Parser e s Word#
unboxWord32 (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word32)
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#))
-> Parser e s Word#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word32)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e Word32
r #) -> case Result# e Word32
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# W32# Word#
a, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# Word#
a, Int#
b, Int#
c #) #) #)
)
unboxIntPair :: Parser e s (Int,Int) -> Parser e s (# Int#, Int# #)
{-# inline unboxIntPair #-}
unboxIntPair :: Parser e s (Int, Int) -> Parser e s (# Int#, Int# #)
unboxIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e (Int, Int))
f) = ((# ByteArray#, Int#, Int# #)
-> ST# s (Result# e (# Int#, Int# #)))
-> Parser e s (# Int#, Int# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e (Int, Int))
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e (Int, Int)
r #) -> case Result# e (Int, Int)
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# (I# Int#
y, I# Int#
z), Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# (# Int#
y, Int#
z #), Int#
b, Int#
c #) #) #)
)
boxWord32 :: Parser e s Word# -> Parser e s Word32
{-# inline boxWord32 #-}
boxWord32 :: Parser e s Word# -> Parser e s Word32
boxWord32 (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#)
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word32))
-> Parser e s Word32
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Word#)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e Word#
r #) -> case Result# e Word#
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# Word#
a, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# Word# -> Word32
W32# Word#
a, Int#
b, Int#
c #) #) #)
)
boxInt :: Parser e s Int# -> Parser e s Int
{-# inline boxInt #-}
boxInt :: Parser e s Int# -> Parser e s Int
boxInt (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#)
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int))
-> Parser e s Int
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e Int#
r #) -> case Result# e Int#
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# Int#
y, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# Int# -> Int
I# Int#
y, Int#
b, Int#
c #) #) #)
)
boxBool :: Parser e s Int# -> Parser e s Bool
{-# inline boxBool #-}
boxBool :: Parser e s Int# -> Parser e s Bool
boxBool (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#)
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Bool))
-> Parser e s Bool
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e Int#
r #) -> case Result# e Int#
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# Int#
y, Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# case Int#
y of {Int#
1# -> Bool
True; Int#
_ -> Bool
False}, Int#
b, Int#
c #) #) #)
)
boxIntPair :: Parser e s (# Int#, Int# #) -> Parser e s (Int,Int)
{-# inline boxIntPair #-}
boxIntPair :: Parser e s (# Int#, Int# #) -> Parser e s (Int, Int)
boxIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e (# Int#, Int# #))
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e (Int, Int)))
-> Parser e s (Int, Int)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e (# Int#, Int# #))
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e (# Int#, Int# #)
r #) -> case Result# e (# Int#, Int# #)
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# (# Int#
y, Int#
z #), Int#
b, Int#
c #) #) -> (# State# s
s1, (# | (# (Int# -> Int
I# Int#
y, Int# -> Int
I# Int#
z), Int#
b, Int#
c #) #) #)
)
infixl 3 `orElse`
orElse :: Parser x s a -> Parser e s a -> Parser e s a
{-# inline orElse #-}
orElse :: Parser x s a -> Parser e s a -> Parser e s a
orElse (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# x a)
f) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
g) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#, Int#, Int# #)
x State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# x a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# x a
r0 #) -> case Result# x a
r0 of
(# x
_ | #) -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
g (# ByteArray#, Int#, Int# #)
x State# s
s1
(# | (# a, Int#, Int# #)
r #) -> (# State# s
s1, (# | (# a, Int#, Int# #)
r #) #)
)
bindFromCharToLifted :: Parser s e Char# -> (Char# -> Parser s e a) -> Parser s e a
{-# inline bindFromCharToLifted #-}
bindFromCharToLifted :: Parser s e Char# -> (Char# -> Parser s e a) -> Parser s e a
bindFromCharToLifted (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s Char#)
f) Char# -> Parser s e a
g = ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s a))
-> Parser s e a
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s Char#)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
(# State# e
s1, Result# s Char#
r0 #) -> case Result# s Char#
r0 of
(# s
e | #) -> (# State# e
s1, (# s
e | #) #)
(# | (# Char#
y, Int#
b, Int#
c #) #) ->
Parser s e a -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (Char# -> Parser s e a
g Char#
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
)
bindFromCharToIntPair :: Parser s e Char# -> (Char# -> Parser s e (# Int#, Int# #)) -> Parser s e (# Int#, Int# #)
{-# inline bindFromCharToIntPair #-}
bindFromCharToIntPair :: Parser s e Char#
-> (Char# -> Parser s e (# Int#, Int# #))
-> Parser s e (# Int#, Int# #)
bindFromCharToIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s Char#)
f) Char# -> Parser s e (# Int#, Int# #)
g = ((# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #)))
-> Parser s e (# Int#, Int# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s Char#)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
(# State# e
s1, Result# s Char#
r0 #) -> case Result# s Char#
r0 of
(# s
e | #) -> (# State# e
s1, (# s
e | #) #)
(# | (# Char#
y, Int#
b, Int#
c #) #) ->
Parser s e (# Int#, Int# #)
-> (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #))
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (Char# -> Parser s e (# Int#, Int# #)
g Char#
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
)
bindFromLiftedToInt :: Parser s e a -> (a -> Parser s e Int#) -> Parser s e Int#
{-# inline bindFromLiftedToInt #-}
bindFromLiftedToInt :: Parser s e a -> (a -> Parser s e Int#) -> Parser s e Int#
bindFromLiftedToInt (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) a -> Parser s e Int#
g = ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s Int#))
-> Parser s e Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
(# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
(# s
e | #) -> (# State# e
s1, (# s
e | #) #)
(# | (# a
y, Int#
b, Int#
c #) #) ->
Parser s e Int#
-> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s Int#)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser s e Int#
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
)
bindFromLiftedToIntPair :: Parser s e a -> (a -> Parser s e (# Int#, Int# #)) -> Parser s e (# Int#, Int# #)
{-# inline bindFromLiftedToIntPair #-}
bindFromLiftedToIntPair :: Parser s e a
-> (a -> Parser s e (# Int#, Int# #))
-> Parser s e (# Int#, Int# #)
bindFromLiftedToIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f) a -> Parser s e (# Int#, Int# #)
g = ((# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #)))
-> Parser s e (# Int#, Int# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
(# State# e
s1, Result# s a
r0 #) -> case Result# s a
r0 of
(# s
e | #) -> (# State# e
s1, (# s
e | #) #)
(# | (# a
y, Int#
b, Int#
c #) #) ->
Parser s e (# Int#, Int# #)
-> (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #))
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (a -> Parser s e (# Int#, Int# #)
g a
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
)
bindFromIntToIntPair :: Parser s e Int# -> (Int# -> Parser s e (# Int#, Int# #)) -> Parser s e (# Int#, Int# #)
{-# inline bindFromIntToIntPair #-}
bindFromIntToIntPair :: Parser s e Int#
-> (Int# -> Parser s e (# Int#, Int# #))
-> Parser s e (# Int#, Int# #)
bindFromIntToIntPair (Parser (# ByteArray#, Int#, Int# #) -> ST# e (Result# s Int#)
f) Int# -> Parser s e (# Int#, Int# #)
g = ((# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #)))
-> Parser s e (# Int#, Int# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# e (Result# s Int#)
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
(# State# e
s1, Result# s Int#
r0 #) -> case Result# s Int#
r0 of
(# s
e | #) -> (# State# e
s1, (# s
e | #) #)
(# | (# Int#
y, Int#
b, Int#
c #) #) ->
Parser s e (# Int#, Int# #)
-> (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #))
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser (Int# -> Parser s e (# Int#, Int# #)
g Int#
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
)
bindFromMaybeCharToIntPair ::
Parser s e (# (# #) | Char# #)
-> ((# (# #) | Char# #) -> Parser s e (# Int#, Int# #))
-> Parser s e (# Int#, Int# #)
{-# inline bindFromMaybeCharToIntPair #-}
bindFromMaybeCharToIntPair :: Parser s e (# (# #) | Char# #)
-> ((# (# #) | Char# #) -> Parser s e (# Int#, Int# #))
-> Parser s e (# Int#, Int# #)
bindFromMaybeCharToIntPair (Parser (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# (# #) | Char# #))
f) (# (# #) | Char# #) -> Parser s e (# Int#, Int# #)
g = ((# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #)))
-> Parser s e (# Int#, Int# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# (# #) | Char# #))
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
(# State# e
s1, Result# s (# (# #) | Char# #)
r0 #) -> case Result# s (# (# #) | Char# #)
r0 of
(# s
e | #) -> (# State# e
s1, (# s
e | #) #)
(# | (# (# (# #) | Char# #)
y, Int#
b, Int#
c #) #) ->
Parser s e (# Int#, Int# #)
-> (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #))
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser ((# (# #) | Char# #) -> Parser s e (# Int#, Int# #)
g (# (# #) | Char# #)
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
)
bindFromMaybeCharToLifted ::
Parser s e (# (# #) | Char# #)
-> ((# (# #) | Char# #) -> Parser s e a)
-> Parser s e a
{-# inline bindFromMaybeCharToLifted #-}
bindFromMaybeCharToLifted :: Parser s e (# (# #) | Char# #)
-> ((# (# #) | Char# #) -> Parser s e a) -> Parser s e a
bindFromMaybeCharToLifted (Parser (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# (# #) | Char# #))
f) (# (# #) | Char# #) -> Parser s e a
g = ((# ByteArray#, Int#, Int# #) -> ST# e (Result# s a))
-> Parser s e a
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
arr, Int#
_, Int#
_ #) State# e
s0 -> case (# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# (# #) | Char# #))
f (# ByteArray#, Int#, Int# #)
x State# e
s0 of
(# State# e
s1, Result# s (# (# #) | Char# #)
r0 #) -> case Result# s (# (# #) | Char# #)
r0 of
(# s
e | #) -> (# State# e
s1, (# s
e | #) #)
(# | (# (# (# #) | Char# #)
y, Int#
b, Int#
c #) #) ->
Parser s e a -> (# ByteArray#, Int#, Int# #) -> ST# e (Result# s a)
forall e s a.
Parser e s a -> (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
runParser ((# (# #) | Char# #) -> Parser s e a
g (# (# #) | Char# #)
y) (# ByteArray#
arr, Int#
b, Int#
c #) State# e
s1
)
pureIntPair ::
(# Int#, Int# #)
-> Parser s e (# Int#, Int# #)
{-# inline pureIntPair #-}
pureIntPair :: (# Int#, Int# #) -> Parser s e (# Int#, Int# #)
pureIntPair (# Int#, Int# #)
a = ((# ByteArray#, Int#, Int# #)
-> ST# e (Result# s (# Int#, Int# #)))
-> Parser s e (# Int#, Int# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#
_, Int#
b, Int#
c #) State# e
s -> (# State# e
s, (# | (# (# Int#, Int# #)
a, Int#
b, Int#
c #) #) #))
failIntPair :: e -> Parser e s (# Int#, Int# #)
{-# inline failIntPair #-}
failIntPair :: e -> Parser e s (# Int#, Int# #)
failIntPair e
e = ((# ByteArray#, Int#, Int# #)
-> ST# s (Result# e (# Int#, Int# #)))
-> Parser e s (# Int#, Int# #)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\(# ByteArray#
_, Int#
_, Int#
_ #) State# s
s -> (# State# s
s, (# e
e | #) #))
measure :: Parser e s a -> Parser e s (Int,a)
{-# inline measure #-}
measure :: Parser e s a -> Parser e s (Int, a)
measure (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e (Int, a)))
-> Parser e s (Int, a)
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
_, Int#
pre, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e a
r #) -> case Result# e a
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# a
y, Int#
post, Int#
c #) #) -> (# State# s
s1, (# | (# (Int# -> Int
I# (Int#
post Int# -> Int# -> Int#
-# Int#
pre), a
y),Int#
post,Int#
c #) #) #)
)
measure_ :: Parser e s a -> Parser e s Int
{-# inline measure_ #-}
measure_ :: Parser e s a -> Parser e s Int
measure_ Parser e s a
p = Parser e s Int# -> Parser e s Int
forall e s. Parser e s Int# -> Parser e s Int
boxInt (Parser e s a -> Parser e s Int#
forall e s a. Parser e s a -> Parser e s Int#
measure_# Parser e s a
p)
measure_# :: Parser e s a -> Parser e s Int#
{-# inline measure_# #-}
measure_# :: Parser e s a -> Parser e s Int#
measure_# (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e Int#))
-> Parser e s Int#
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
(\x :: (# ByteArray#, Int#, Int# #)
x@(# ByteArray#
_, Int#
pre, Int#
_ #) State# s
s0 -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#, Int#, Int# #)
x State# s
s0 of
(# State# s
s1, Result# e a
r #) -> case Result# e a
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# a
_, Int#
post, Int#
c #) #) -> (# State# s
s1, (# | (# Int#
post Int# -> Int# -> Int#
-# Int#
pre,Int#
post,Int#
c #) #) #)
)
delimit ::
e
-> e
-> Int
-> Parser e s a
-> Parser e s a
{-# inline delimit #-}
delimit :: e -> e -> Int -> Parser e s a -> Parser e s a
delimit e
esz e
eleftovers (I# Int#
n) (Parser (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f) = ((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
forall e s a.
((# ByteArray#, Int#, Int# #) -> ST# s (Result# e a))
-> Parser e s a
Parser
( \(# ByteArray#
arr, Int#
off, Int#
len #) State# s
s0 -> case Int#
len Int# -> Int# -> Int#
>=# Int#
n of
Int#
1# -> case (# ByteArray#, Int#, Int# #) -> ST# s (Result# e a)
f (# ByteArray#
arr, Int#
off, Int#
n #) State# s
s0 of
(# State# s
s1, Result# e a
r #) -> case Result# e a
r of
(# e
e | #) -> (# State# s
s1, (# e
e | #) #)
(# | (# a
a, Int#
newOff, Int#
leftovers #) #) -> case Int#
leftovers of
Int#
0# -> (# State# s
s1, (# | (# a
a, Int#
newOff, Int#
len Int# -> Int# -> Int#
-# Int#
n #) #) #)
Int#
_ -> (# State# s
s1, (# e
eleftovers | #) #)
Int#
_ -> (# State# s
s0, (# e
esz | #) #)
)
replicate :: forall arr e s a. (Contiguous arr, Element arr a)
=> Int
-> Parser e s a
-> Parser e s (arr a)
{-# inline replicate #-}
replicate :: Int -> Parser e s a -> Parser e s (arr a)
replicate !Int
len Parser e s a
p = do
Mutable arr s a
marr <- ST s (Mutable arr s a) -> Parser e s (Mutable arr s a)
forall s a e. ST s a -> Parser e s a
effect (Int -> ST s (Mutable arr (PrimState (ST s)) a)
forall (arr :: * -> *) (m :: * -> *) b.
(Contiguous arr, PrimMonad m, Element arr b) =>
Int -> m (Mutable arr (PrimState m) b)
C.new Int
len)
let go :: Int -> Parser e s (arr a)
go :: Int -> Parser e s (arr a)
go !Int
ix = if Int
ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
len
then do
a
a <- Parser e s a
p
ST s () -> Parser e s ()
forall s a e. ST s a -> Parser e s a
effect (Mutable arr (PrimState (ST s)) a -> Int -> a -> ST s ()
forall (arr :: * -> *) (m :: * -> *) b.
(Contiguous arr, PrimMonad m, Element arr b) =>
Mutable arr (PrimState m) b -> Int -> b -> m ()
C.write Mutable arr s a
Mutable arr (PrimState (ST s)) a
marr Int
ix a
a)
Int -> Parser e s (arr a)
go (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
else ST s (arr a) -> Parser e s (arr a)
forall s a e. ST s a -> Parser e s a
effect (Mutable arr (PrimState (ST s)) a -> ST s (arr a)
forall (arr :: * -> *) (m :: * -> *) b.
(Contiguous arr, PrimMonad m, Element arr b) =>
Mutable arr (PrimState m) b -> m (arr b)
C.unsafeFreeze Mutable arr s a
Mutable arr (PrimState (ST s)) a
marr)
Int -> Parser e s (arr a)
go Int
0
unI :: Int -> Int#
{-# inline unI #-}
unI :: Int -> Int#
unI (I# Int#
w) = Int#
w