{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-}
module Codec.CBOR.Decoding
(
Decoder
, DecodeAction(..)
, liftST
, getDecodeAction
, decodeWord
, decodeWord8
, decodeWord16
, decodeWord32
, decodeWord64
, decodeNegWord
, decodeNegWord64
, decodeInt
, decodeInt8
, decodeInt16
, decodeInt32
, decodeInt64
, decodeInteger
, decodeFloat
, decodeDouble
, decodeBytes
, decodeBytesIndef
, decodeByteArray
, decodeString
, decodeStringIndef
, decodeUtf8ByteArray
, decodeListLen
, decodeListLenIndef
, decodeMapLen
, decodeMapLenIndef
, decodeTag
, decodeTag64
, decodeBool
, decodeNull
, decodeSimple
, decodeWordOf
, decodeListLenOf
, decodeListLenOrIndef
, decodeMapLenOrIndef
, decodeBreakOr
, peekTokenType
, TokenType(..)
, peekAvailable
, ByteOffset
, peekByteOffset
, decodeWithByteSpan
, decodeWordCanonical
, decodeWord8Canonical
, decodeWord16Canonical
, decodeWord32Canonical
, decodeWord64Canonical
, decodeNegWordCanonical
, decodeNegWord64Canonical
, decodeIntCanonical
, decodeInt8Canonical
, decodeInt16Canonical
, decodeInt32Canonical
, decodeInt64Canonical
, decodeBytesCanonical
, decodeByteArrayCanonical
, decodeStringCanonical
, decodeUtf8ByteArrayCanonical
, decodeListLenCanonical
, decodeMapLenCanonical
, decodeTagCanonical
, decodeTag64Canonical
, decodeIntegerCanonical
, decodeFloat16Canonical
, decodeFloatCanonical
, decodeDoubleCanonical
, decodeSimpleCanonical
, decodeWordCanonicalOf
, decodeListLenCanonicalOf
, decodeSequenceLenIndef
, decodeSequenceLenN
) where
#include "cbor.h"
import GHC.Exts
import GHC.Word
import GHC.Int
import Data.Text (Text)
import Data.ByteString (ByteString)
import Control.Applicative
import Control.Monad.ST
import qualified Control.Monad.Fail as Fail
import Codec.CBOR.ByteArray (ByteArray)
import Prelude hiding (decodeFloat)
newtype Decoder s a = Decoder {
forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder :: forall r. (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
}
data DecodeAction s a
= ConsumeWord (Word# -> ST s (DecodeAction s a))
| ConsumeWord8 (Word# -> ST s (DecodeAction s a))
| ConsumeWord16 (Word# -> ST s (DecodeAction s a))
| ConsumeWord32 (Word# -> ST s (DecodeAction s a))
| ConsumeNegWord (Word# -> ST s (DecodeAction s a))
| ConsumeInt (Int# -> ST s (DecodeAction s a))
| ConsumeInt8 (Int# -> ST s (DecodeAction s a))
| ConsumeInt16 (Int# -> ST s (DecodeAction s a))
| ConsumeInt32 (Int# -> ST s (DecodeAction s a))
| ConsumeListLen (Int# -> ST s (DecodeAction s a))
| ConsumeMapLen (Int# -> ST s (DecodeAction s a))
| ConsumeTag (Word# -> ST s (DecodeAction s a))
#if defined(ARCH_32bit)
| ConsumeWord64 (Word64# -> ST s (DecodeAction s a))
| ConsumeNegWord64 (Word64# -> ST s (DecodeAction s a))
| ConsumeInt64 (Int64# -> ST s (DecodeAction s a))
| ConsumeListLen64 (Int64# -> ST s (DecodeAction s a))
| ConsumeMapLen64 (Int64# -> ST s (DecodeAction s a))
| ConsumeTag64 (Word64# -> ST s (DecodeAction s a))
#endif
| ConsumeInteger (Integer -> ST s (DecodeAction s a))
| ConsumeFloat (Float# -> ST s (DecodeAction s a))
| ConsumeDouble (Double# -> ST s (DecodeAction s a))
| ConsumeBytes (ByteString-> ST s (DecodeAction s a))
| ConsumeByteArray (ByteArray -> ST s (DecodeAction s a))
| ConsumeString (Text -> ST s (DecodeAction s a))
| ConsumeUtf8ByteArray (ByteArray -> ST s (DecodeAction s a))
| ConsumeBool (Bool -> ST s (DecodeAction s a))
| ConsumeSimple (Word# -> ST s (DecodeAction s a))
| ConsumeBytesIndef (ST s (DecodeAction s a))
| ConsumeStringIndef (ST s (DecodeAction s a))
| ConsumeListLenIndef (ST s (DecodeAction s a))
| ConsumeMapLenIndef (ST s (DecodeAction s a))
| (ST s (DecodeAction s a))
| ConsumeListLenOrIndef (Int# -> ST s (DecodeAction s a))
| ConsumeMapLenOrIndef (Int# -> ST s (DecodeAction s a))
| ConsumeBreakOr (Bool -> ST s (DecodeAction s a))
| PeekTokenType (TokenType -> ST s (DecodeAction s a))
| PeekAvailable (Int# -> ST s (DecodeAction s a))
#if defined(ARCH_32bit)
| PeekByteOffset (Int64# -> ST s (DecodeAction s a))
#else
| PeekByteOffset (Int# -> ST s (DecodeAction s a))
#endif
| ConsumeWordCanonical (Word# -> ST s (DecodeAction s a))
| ConsumeWord8Canonical (Word# -> ST s (DecodeAction s a))
| ConsumeWord16Canonical (Word# -> ST s (DecodeAction s a))
| ConsumeWord32Canonical (Word# -> ST s (DecodeAction s a))
| ConsumeNegWordCanonical (Word# -> ST s (DecodeAction s a))
| ConsumeIntCanonical (Int# -> ST s (DecodeAction s a))
| ConsumeInt8Canonical (Int# -> ST s (DecodeAction s a))
| ConsumeInt16Canonical (Int# -> ST s (DecodeAction s a))
| ConsumeInt32Canonical (Int# -> ST s (DecodeAction s a))
| ConsumeListLenCanonical (Int# -> ST s (DecodeAction s a))
| ConsumeMapLenCanonical (Int# -> ST s (DecodeAction s a))
| ConsumeTagCanonical (Word# -> ST s (DecodeAction s a))
#if defined(ARCH_32bit)
| ConsumeWord64Canonical (Word64# -> ST s (DecodeAction s a))
| ConsumeNegWord64Canonical (Word64# -> ST s (DecodeAction s a))
| ConsumeInt64Canonical (Int64# -> ST s (DecodeAction s a))
| ConsumeListLen64Canonical (Int64# -> ST s (DecodeAction s a))
| ConsumeMapLen64Canonical (Int64# -> ST s (DecodeAction s a))
| ConsumeTag64Canonical (Word64# -> ST s (DecodeAction s a))
#endif
| ConsumeIntegerCanonical (Integer -> ST s (DecodeAction s a))
| ConsumeFloat16Canonical (Float# -> ST s (DecodeAction s a))
| ConsumeFloatCanonical (Float# -> ST s (DecodeAction s a))
| ConsumeDoubleCanonical (Double# -> ST s (DecodeAction s a))
| ConsumeBytesCanonical (ByteString-> ST s (DecodeAction s a))
| ConsumeByteArrayCanonical (ByteArray -> ST s (DecodeAction s a))
| ConsumeStringCanonical (Text -> ST s (DecodeAction s a))
| ConsumeUtf8ByteArrayCanonical (ByteArray -> ST s (DecodeAction s a))
| ConsumeSimpleCanonical (Word# -> ST s (DecodeAction s a))
| Fail String
| Done a
data TokenType
= TypeUInt
| TypeUInt64
| TypeNInt
| TypeNInt64
| TypeInteger
| TypeFloat16
| TypeFloat32
| TypeFloat64
| TypeBytes
| TypeBytesIndef
| TypeString
| TypeStringIndef
| TypeListLen
| TypeListLen64
| TypeListLenIndef
| TypeMapLen
| TypeMapLen64
| TypeMapLenIndef
| TypeTag
| TypeTag64
| TypeBool
| TypeNull
| TypeSimple
| TypeBreak
| TypeInvalid
deriving (TokenType -> TokenType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenType -> TokenType -> Bool
$c/= :: TokenType -> TokenType -> Bool
== :: TokenType -> TokenType -> Bool
$c== :: TokenType -> TokenType -> Bool
Eq, Eq TokenType
TokenType -> TokenType -> Bool
TokenType -> TokenType -> Ordering
TokenType -> TokenType -> TokenType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TokenType -> TokenType -> TokenType
$cmin :: TokenType -> TokenType -> TokenType
max :: TokenType -> TokenType -> TokenType
$cmax :: TokenType -> TokenType -> TokenType
>= :: TokenType -> TokenType -> Bool
$c>= :: TokenType -> TokenType -> Bool
> :: TokenType -> TokenType -> Bool
$c> :: TokenType -> TokenType -> Bool
<= :: TokenType -> TokenType -> Bool
$c<= :: TokenType -> TokenType -> Bool
< :: TokenType -> TokenType -> Bool
$c< :: TokenType -> TokenType -> Bool
compare :: TokenType -> TokenType -> Ordering
$ccompare :: TokenType -> TokenType -> Ordering
Ord, Int -> TokenType
TokenType -> Int
TokenType -> [TokenType]
TokenType -> TokenType
TokenType -> TokenType -> [TokenType]
TokenType -> TokenType -> TokenType -> [TokenType]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TokenType -> TokenType -> TokenType -> [TokenType]
$cenumFromThenTo :: TokenType -> TokenType -> TokenType -> [TokenType]
enumFromTo :: TokenType -> TokenType -> [TokenType]
$cenumFromTo :: TokenType -> TokenType -> [TokenType]
enumFromThen :: TokenType -> TokenType -> [TokenType]
$cenumFromThen :: TokenType -> TokenType -> [TokenType]
enumFrom :: TokenType -> [TokenType]
$cenumFrom :: TokenType -> [TokenType]
fromEnum :: TokenType -> Int
$cfromEnum :: TokenType -> Int
toEnum :: Int -> TokenType
$ctoEnum :: Int -> TokenType
pred :: TokenType -> TokenType
$cpred :: TokenType -> TokenType
succ :: TokenType -> TokenType
$csucc :: TokenType -> TokenType
Enum, TokenType
forall a. a -> a -> Bounded a
maxBound :: TokenType
$cmaxBound :: TokenType
minBound :: TokenType
$cminBound :: TokenType
Bounded, Int -> TokenType -> ShowS
[TokenType] -> ShowS
TokenType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenType] -> ShowS
$cshowList :: [TokenType] -> ShowS
show :: TokenType -> String
$cshow :: TokenType -> String
showsPrec :: Int -> TokenType -> ShowS
$cshowsPrec :: Int -> TokenType -> ShowS
Show)
instance Functor (Decoder s) where
{-# INLINE fmap #-}
fmap :: forall a b. (a -> b) -> Decoder s a -> Decoder s b
fmap a -> b
f = \Decoder s a
d -> forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k -> forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
d (b -> ST s (DecodeAction s r)
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)
instance Applicative (Decoder s) where
{-# INLINE pure #-}
pure :: forall a. a -> Decoder s a
pure = \a
x -> forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder forall a b. (a -> b) -> a -> b
$ \a -> ST s (DecodeAction s r)
k -> a -> ST s (DecodeAction s r)
k a
x
{-# INLINE (<*>) #-}
<*> :: forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
(<*>) = \Decoder s (a -> b)
df Decoder s a
dx -> forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k ->
forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s (a -> b)
df (\a -> b
f -> forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
dx (\a
x -> b -> ST s (DecodeAction s r)
k (a -> b
f a
x)))
{-# INLINE (*>) #-}
*> :: forall a b. Decoder s a -> Decoder s b -> Decoder s b
(*>) = \Decoder s a
dm Decoder s b
dn -> forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k -> forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
dm (\a
_ -> forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s b
dn b -> ST s (DecodeAction s r)
k)
instance Monad (Decoder s) where
return :: forall a. a -> Decoder s a
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE (>>=) #-}
>>= :: forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
(>>=) = \Decoder s a
dm a -> Decoder s b
f -> forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder forall a b. (a -> b) -> a -> b
$ \b -> ST s (DecodeAction s r)
k -> forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder Decoder s a
dm (\a
m -> forall s a.
Decoder s a
-> forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
runDecoder (a -> Decoder s b
f a
m) b -> ST s (DecodeAction s r)
k)
{-# INLINE (>>) #-}
>> :: forall a b. Decoder s a -> Decoder s b -> Decoder s b
(>>) = forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
#if !MIN_VERSION_base(4,13,0)
fail = Fail.fail
#endif
instance Fail.MonadFail (Decoder s) where
fail :: forall a. String -> Decoder s a
fail String
msg = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder forall a b. (a -> b) -> a -> b
$ \a -> ST s (DecodeAction s r)
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. String -> DecodeAction s a
Fail String
msg)
liftST :: ST s a -> Decoder s a
liftST :: forall s a. ST s a -> Decoder s a
liftST ST s a
m = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder forall a b. (a -> b) -> a -> b
$ \a -> ST s (DecodeAction s r)
k -> ST s a
m forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= a -> ST s (DecodeAction s r)
k
getDecodeAction :: Decoder s a -> ST s (DecodeAction s a)
getDecodeAction :: forall s a. Decoder s a -> ST s (DecodeAction s a)
getDecodeAction (Decoder forall r. (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
k) = forall r. (a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r)
k (\a
x -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. a -> DecodeAction s a
Done a
x))
toInt8 :: Int# -> Int8
toInt16 :: Int# -> Int16
toInt32 :: Int# -> Int32
toInt64 :: Int# -> Int64
toWord8 :: Word# -> Word8
toWord16 :: Word# -> Word16
toWord32 :: Word# -> Word32
toWord64 :: Word# -> Word64
#if MIN_VERSION_ghc_prim(0,8,0)
toInt8 :: Int# -> Int8
toInt8 Int#
n = Int8# -> Int8
I8# (Int# -> Int8#
intToInt8# Int#
n)
toInt16 :: Int# -> Int16
toInt16 Int#
n = Int16# -> Int16
I16# (Int# -> Int16#
intToInt16# Int#
n)
toInt32 :: Int# -> Int32
toInt32 Int#
n = Int32# -> Int32
I32# (Int# -> Int32#
intToInt32# Int#
n)
toWord8 :: Word# -> Word8
toWord8 Word#
n = Word8# -> Word8
W8# (Word# -> Word8#
wordToWord8# Word#
n)
toWord16 :: Word# -> Word16
toWord16 Word#
n = Word16# -> Word16
W16# (Word# -> Word16#
wordToWord16# Word#
n)
toWord32 :: Word# -> Word32
toWord32 Word#
n = Word32# -> Word32
W32# (Word# -> Word32#
wordToWord32# Word#
n)
#if WORD_SIZE_IN_BITS == 64
#if MIN_VERSION_base(4,17,0)
toInt64 n = I64# (intToInt64# n)
toWord64 n = W64# (wordToWord64# n)
#else
toInt64 :: Int# -> Int64
toInt64 Int#
n = Int# -> Int64
I64# Int#
n
toWord64 :: Word# -> Word64
toWord64 Word#
n = Word# -> Word64
W64# Word#
n
#endif
#else
toInt64 n = I64# (intToInt64# n)
toWord64 n = W64# (wordToWord64# n)
#endif
#else
toInt8 n = I8# n
toInt16 n = I16# n
toInt32 n = I32# n
toInt64 n = I64# n
toWord8 n = W8# n
toWord16 n = W16# n
toWord32 n = W32# n
toWord64 n = W64# n
#endif
decodeWord :: Decoder s Word
decodeWord :: forall s. Decoder s Word
decodeWord = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeWord #-}
decodeWord8 :: Decoder s Word8
decodeWord8 :: forall s. Decoder s Word8
decodeWord8 = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord8 (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
toWord8 Word#
w#))))
{-# INLINE decodeWord8 #-}
decodeWord16 :: Decoder s Word16
decodeWord16 :: forall s. Decoder s Word16
decodeWord16 = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word16 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord16 (\Word#
w# -> Word16 -> ST s (DecodeAction s r)
k (Word# -> Word16
toWord16 Word#
w#))))
{-# INLINE decodeWord16 #-}
decodeWord32 :: Decoder s Word32
decodeWord32 :: forall s. Decoder s Word32
decodeWord32 = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word32 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord32 (\Word#
w# -> Word32 -> ST s (DecodeAction s r)
k (Word# -> Word32
toWord32 Word#
w#))))
{-# INLINE decodeWord32 #-}
decodeWord64 :: Decoder s Word64
{-# INLINE decodeWord64 #-}
decodeWord64 :: forall s. Decoder s Word64
decodeWord64 =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
toWord64 Word#
w#))))
#else
Decoder (\k -> return (ConsumeWord64 (\w64# -> k (toWord64 w64#))))
#endif
decodeNegWord :: Decoder s Word
decodeNegWord :: forall s. Decoder s Word
decodeNegWord = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWord (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeNegWord #-}
decodeNegWord64 :: Decoder s Word64
{-# INLINE decodeNegWord64 #-}
decodeNegWord64 :: forall s. Decoder s Word64
decodeNegWord64 =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWord (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
toWord64 Word#
w#))))
#else
Decoder (\k -> return (ConsumeNegWord64 (\w64# -> k (toWord64 w64#))))
#endif
decodeInt :: Decoder s Int
decodeInt :: forall s. Decoder s Int
decodeInt = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeInt #-}
decodeInt8 :: Decoder s Int8
decodeInt8 :: forall s. Decoder s Int8
decodeInt8 = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int8 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt8 (\Int#
w# -> Int8 -> ST s (DecodeAction s r)
k (Int# -> Int8
toInt8 Int#
w#))))
{-# INLINE decodeInt8 #-}
decodeInt16 :: Decoder s Int16
decodeInt16 :: forall s. Decoder s Int16
decodeInt16 = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int16 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt16 (\Int#
w# -> Int16 -> ST s (DecodeAction s r)
k (Int# -> Int16
toInt16 Int#
w#))))
{-# INLINE decodeInt16 #-}
decodeInt32 :: Decoder s Int32
decodeInt32 :: forall s. Decoder s Int32
decodeInt32 = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int32 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt32 (\Int#
w# -> Int32 -> ST s (DecodeAction s r)
k (Int# -> Int32
toInt32 Int#
w#))))
{-# INLINE decodeInt32 #-}
decodeInt64 :: Decoder s Int64
{-# INLINE decodeInt64 #-}
decodeInt64 :: forall s. Decoder s Int64
decodeInt64 =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt (\Int#
n# -> Int64 -> ST s (DecodeAction s r)
k (Int# -> Int64
toInt64 Int#
n#))))
#else
Decoder (\k -> return (ConsumeInt64 (\n64# -> k (toInt64 n64#))))
#endif
decodeWordCanonical :: Decoder s Word
decodeWordCanonical :: forall s. Decoder s Word
decodeWordCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWordCanonical (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeWordCanonical #-}
decodeWord8Canonical :: Decoder s Word8
decodeWord8Canonical :: forall s. Decoder s Word8
decodeWord8Canonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord8Canonical (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
toWord8 Word#
w#))))
{-# INLINE decodeWord8Canonical #-}
decodeWord16Canonical :: Decoder s Word16
decodeWord16Canonical :: forall s. Decoder s Word16
decodeWord16Canonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word16 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord16Canonical (\Word#
w# -> Word16 -> ST s (DecodeAction s r)
k (Word# -> Word16
toWord16 Word#
w#))))
{-# INLINE decodeWord16Canonical #-}
decodeWord32Canonical :: Decoder s Word32
decodeWord32Canonical :: forall s. Decoder s Word32
decodeWord32Canonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word32 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWord32Canonical (\Word#
w# -> Word32 -> ST s (DecodeAction s r)
k (Word# -> Word32
toWord32 Word#
w#))))
{-# INLINE decodeWord32Canonical #-}
decodeWord64Canonical :: Decoder s Word64
{-# INLINE decodeWord64Canonical #-}
decodeWord64Canonical :: forall s. Decoder s Word64
decodeWord64Canonical =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeWordCanonical (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
toWord64 Word#
w#))))
#else
Decoder (\k -> return (ConsumeWord64Canonical (\w64# -> k (toWord64 w64#))))
#endif
decodeNegWordCanonical :: Decoder s Word
decodeNegWordCanonical :: forall s. Decoder s Word
decodeNegWordCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWordCanonical (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeNegWordCanonical #-}
decodeNegWord64Canonical :: Decoder s Word64
{-# INLINE decodeNegWord64Canonical #-}
decodeNegWord64Canonical :: forall s. Decoder s Word64
decodeNegWord64Canonical =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeNegWordCanonical (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
toWord64 Word#
w#))))
#else
Decoder (\k -> return (ConsumeNegWord64Canonical (\w64# -> k (toWord64 w64#))))
#endif
decodeIntCanonical :: Decoder s Int
decodeIntCanonical :: forall s. Decoder s Int
decodeIntCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeIntCanonical (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeIntCanonical #-}
decodeInt8Canonical :: Decoder s Int8
decodeInt8Canonical :: forall s. Decoder s Int8
decodeInt8Canonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int8 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt8Canonical (\Int#
w# -> Int8 -> ST s (DecodeAction s r)
k (Int# -> Int8
toInt8 Int#
w#))))
{-# INLINE decodeInt8Canonical #-}
decodeInt16Canonical :: Decoder s Int16
decodeInt16Canonical :: forall s. Decoder s Int16
decodeInt16Canonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int16 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt16Canonical (\Int#
w# -> Int16 -> ST s (DecodeAction s r)
k (Int# -> Int16
toInt16 Int#
w#))))
{-# INLINE decodeInt16Canonical #-}
decodeInt32Canonical :: Decoder s Int32
decodeInt32Canonical :: forall s. Decoder s Int32
decodeInt32Canonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int32 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInt32Canonical (\Int#
w# -> Int32 -> ST s (DecodeAction s r)
k (Int# -> Int32
toInt32 Int#
w#))))
{-# INLINE decodeInt32Canonical #-}
decodeInt64Canonical :: Decoder s Int64
{-# INLINE decodeInt64Canonical #-}
decodeInt64Canonical :: forall s. Decoder s Int64
decodeInt64Canonical =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeIntCanonical (\Int#
n# -> Int64 -> ST s (DecodeAction s r)
k (Int# -> Int64
toInt64 Int#
n#))))
#else
Decoder (\k -> return (ConsumeInt64Canonical (\n64# -> k (toInt64 n64#))))
#endif
decodeInteger :: Decoder s Integer
decodeInteger :: forall s. Decoder s Integer
decodeInteger = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Integer -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeInteger (\Integer
n -> Integer -> ST s (DecodeAction s r)
k Integer
n)))
{-# INLINE decodeInteger #-}
decodeFloat :: Decoder s Float
decodeFloat :: forall s. Decoder s Float
decodeFloat = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Float -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Float# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeFloat (\Float#
f# -> Float -> ST s (DecodeAction s r)
k (Float# -> Float
F# Float#
f#))))
{-# INLINE decodeFloat #-}
decodeDouble :: Decoder s Double
decodeDouble :: forall s. Decoder s Double
decodeDouble = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Double -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(Double# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeDouble (\Double#
f# -> Double -> ST s (DecodeAction s r)
k (Double# -> Double
D# Double#
f#))))
{-# INLINE decodeDouble #-}
decodeBytes :: Decoder s ByteString
decodeBytes :: forall s. Decoder s ByteString
decodeBytes = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteString -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytes (\ByteString
bs -> ByteString -> ST s (DecodeAction s r)
k ByteString
bs)))
{-# INLINE decodeBytes #-}
decodeBytesCanonical :: Decoder s ByteString
decodeBytesCanonical :: forall s. Decoder s ByteString
decodeBytesCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteString -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(ByteString -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBytesCanonical (\ByteString
bs -> ByteString -> ST s (DecodeAction s r)
k ByteString
bs)))
{-# INLINE decodeBytesCanonical #-}
decodeBytesIndef :: Decoder s ()
decodeBytesIndef :: forall s. Decoder s ()
decodeBytesIndef = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeBytesIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeBytesIndef #-}
decodeByteArray :: Decoder s ByteArray
decodeByteArray :: forall s. Decoder s ByteArray
decodeByteArray = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeByteArray ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeByteArray #-}
decodeByteArrayCanonical :: Decoder s ByteArray
decodeByteArrayCanonical :: forall s. Decoder s ByteArray
decodeByteArrayCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeByteArrayCanonical ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeByteArrayCanonical #-}
decodeString :: Decoder s Text
decodeString :: forall s. Decoder s Text
decodeString = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Text -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Text -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeString (\Text
str -> Text -> ST s (DecodeAction s r)
k Text
str)))
{-# INLINE decodeString #-}
decodeStringCanonical :: Decoder s Text
decodeStringCanonical :: forall s. Decoder s Text
decodeStringCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Text -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Text -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeStringCanonical (\Text
str -> Text -> ST s (DecodeAction s r)
k Text
str)))
{-# INLINE decodeStringCanonical #-}
decodeStringIndef :: Decoder s ()
decodeStringIndef :: forall s. Decoder s ()
decodeStringIndef = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeStringIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeStringIndef #-}
decodeUtf8ByteArray :: Decoder s ByteArray
decodeUtf8ByteArray :: forall s. Decoder s ByteArray
decodeUtf8ByteArray = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeUtf8ByteArray ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeUtf8ByteArray #-}
decodeUtf8ByteArrayCanonical :: Decoder s ByteArray
decodeUtf8ByteArrayCanonical :: forall s. Decoder s ByteArray
decodeUtf8ByteArrayCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\ByteArray -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(ByteArray -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeUtf8ByteArrayCanonical ByteArray -> ST s (DecodeAction s r)
k))
{-# INLINE decodeUtf8ByteArrayCanonical #-}
decodeListLen :: Decoder s Int
decodeListLen :: forall s. Decoder s Int
decodeListLen = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeListLen (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeListLen #-}
decodeListLenCanonical :: Decoder s Int
decodeListLenCanonical :: forall s. Decoder s Int
decodeListLenCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeListLenCanonical (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeListLenCanonical #-}
decodeListLenIndef :: Decoder s ()
decodeListLenIndef :: forall s. Decoder s ()
decodeListLenIndef = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeListLenIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeListLenIndef #-}
decodeMapLen :: Decoder s Int
decodeMapLen :: forall s. Decoder s Int
decodeMapLen = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeMapLen (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeMapLen #-}
decodeMapLenCanonical :: Decoder s Int
decodeMapLenCanonical :: forall s. Decoder s Int
decodeMapLenCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeMapLenCanonical (\Int#
n# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
n#))))
{-# INLINE decodeMapLenCanonical #-}
decodeMapLenIndef :: Decoder s ()
decodeMapLenIndef :: forall s. Decoder s ()
decodeMapLenIndef = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeMapLenIndef (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeMapLenIndef #-}
decodeTag :: Decoder s Word
decodeTag :: forall s. Decoder s Word
decodeTag = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTag (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeTag #-}
decodeTag64 :: Decoder s Word64
{-# INLINE decodeTag64 #-}
decodeTag64 :: forall s. Decoder s Word64
decodeTag64 =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTag (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64#
#if MIN_VERSION_base(4,17,0)
(wordToWord64# w#)
#else
Word#
w#
#endif
))))
#else
Decoder (\k -> return (ConsumeTag64 (\w64# -> k (W64# w64#))))
#endif
decodeTagCanonical :: Decoder s Word
decodeTagCanonical :: forall s. Decoder s Word
decodeTagCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTagCanonical (\Word#
w# -> Word -> ST s (DecodeAction s r)
k (Word# -> Word
W# Word#
w#))))
{-# INLINE decodeTagCanonical #-}
decodeTag64Canonical :: Decoder s Word64
{-# INLINE decodeTag64Canonical #-}
decodeTag64Canonical :: forall s. Decoder s Word64
decodeTag64Canonical =
#if defined(ARCH_64bit)
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeTagCanonical (\Word#
w# -> Word64 -> ST s (DecodeAction s r)
k (Word# -> Word64
W64#
#if MIN_VERSION_base(4,17,0)
(wordToWord64# w#)
#else
Word#
w#
#endif
))))
#else
Decoder (\k -> return (ConsumeTag64Canonical (\w64# -> k (W64# w64#))))
#endif
decodeBool :: Decoder s Bool
decodeBool :: forall s. Decoder s Bool
decodeBool = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Bool -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Bool -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBool (\Bool
b -> Bool -> ST s (DecodeAction s r)
k Bool
b)))
{-# INLINE decodeBool #-}
decodeNull :: Decoder s ()
decodeNull :: forall s. Decoder s ()
decodeNull = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\() -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. ST s (DecodeAction s a) -> DecodeAction s a
ConsumeNull (() -> ST s (DecodeAction s r)
k ())))
{-# INLINE decodeNull #-}
decodeSimple :: Decoder s Word8
decodeSimple :: forall s. Decoder s Word8
decodeSimple = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeSimple (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
toWord8 Word#
w#))))
{-# INLINE decodeSimple #-}
decodeIntegerCanonical :: Decoder s Integer
decodeIntegerCanonical :: forall s. Decoder s Integer
decodeIntegerCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Integer -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(Integer -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeIntegerCanonical (\Integer
n -> Integer -> ST s (DecodeAction s r)
k Integer
n)))
{-# INLINE decodeIntegerCanonical #-}
decodeFloat16Canonical :: Decoder s Float
decodeFloat16Canonical :: forall s. Decoder s Float
decodeFloat16Canonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Float -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Float# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeFloat16Canonical (\Float#
f# -> Float -> ST s (DecodeAction s r)
k (Float# -> Float
F# Float#
f#))))
{-# INLINE decodeFloat16Canonical #-}
decodeFloatCanonical :: Decoder s Float
decodeFloatCanonical :: forall s. Decoder s Float
decodeFloatCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Float -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Float# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeFloatCanonical (\Float#
f# -> Float -> ST s (DecodeAction s r)
k (Float# -> Float
F# Float#
f#))))
{-# INLINE decodeFloatCanonical #-}
decodeDoubleCanonical :: Decoder s Double
decodeDoubleCanonical :: forall s. Decoder s Double
decodeDoubleCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Double -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(Double# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeDoubleCanonical (\Double#
f# -> Double -> ST s (DecodeAction s r)
k (Double# -> Double
D# Double#
f#))))
{-# INLINE decodeDoubleCanonical #-}
decodeSimpleCanonical :: Decoder s Word8
decodeSimpleCanonical :: forall s. Decoder s Word8
decodeSimpleCanonical = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Word8 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Word# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeSimpleCanonical (\Word#
w# -> Word8 -> ST s (DecodeAction s r)
k (Word# -> Word8
toWord8 Word#
w#))))
{-# INLINE decodeSimpleCanonical #-}
decodeWordOf :: Word
-> Decoder s ()
decodeWordOf :: forall s. Word -> Decoder s ()
decodeWordOf = forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeWordOfHelper forall s. Decoder s Word
decodeWord
{-# INLINE decodeWordOf #-}
decodeListLenOf :: Int -> Decoder s ()
decodeListLenOf :: forall s. Int -> Decoder s ()
decodeListLenOf = forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeListLenOfHelper forall s. Decoder s Int
decodeListLen
{-# INLINE decodeListLenOf #-}
decodeWordCanonicalOf :: Word
-> Decoder s ()
decodeWordCanonicalOf :: forall s. Word -> Decoder s ()
decodeWordCanonicalOf = forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeWordOfHelper forall s. Decoder s Word
decodeWordCanonical
{-# INLINE decodeWordCanonicalOf #-}
decodeListLenCanonicalOf :: Int -> Decoder s ()
decodeListLenCanonicalOf :: forall s. Int -> Decoder s ()
decodeListLenCanonicalOf = forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeListLenOfHelper forall s. Decoder s Int
decodeListLenCanonical
{-# INLINE decodeListLenCanonicalOf #-}
decodeListLenOfHelper :: (Show a, Eq a, Fail.MonadFail m) => m a -> a -> m ()
decodeListLenOfHelper :: forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeListLenOfHelper m a
decodeFun = \a
len -> do
a
len' <- m a
decodeFun
if a
len forall a. Eq a => a -> a -> Bool
== a
len' then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"expected list of length " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
len
{-# INLINE decodeListLenOfHelper #-}
decodeWordOfHelper :: (Show a, Eq a, Fail.MonadFail m) => m a -> a -> m ()
decodeWordOfHelper :: forall a (m :: * -> *).
(Show a, Eq a, MonadFail m) =>
m a -> a -> m ()
decodeWordOfHelper m a
decodeFun = \a
n -> do
a
n' <- m a
decodeFun
if a
n forall a. Eq a => a -> a -> Bool
== a
n' then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"expected word " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
n
{-# INLINE decodeWordOfHelper #-}
decodeListLenOrIndef :: Decoder s (Maybe Int)
decodeListLenOrIndef :: forall s. Decoder s (Maybe Int)
decodeListLenOrIndef =
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Maybe Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeListLenOrIndef (\Int#
n# ->
if Int# -> Int
I# Int#
n# forall a. Ord a => a -> a -> Bool
>= Int
0
then Maybe Int -> ST s (DecodeAction s r)
k (forall a. a -> Maybe a
Just (Int# -> Int
I# Int#
n#))
else Maybe Int -> ST s (DecodeAction s r)
k forall a. Maybe a
Nothing)))
{-# INLINE decodeListLenOrIndef #-}
decodeMapLenOrIndef :: Decoder s (Maybe Int)
decodeMapLenOrIndef :: forall s. Decoder s (Maybe Int)
decodeMapLenOrIndef =
forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Maybe Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeMapLenOrIndef (\Int#
n# ->
if Int# -> Int
I# Int#
n# forall a. Ord a => a -> a -> Bool
>= Int
0
then Maybe Int -> ST s (DecodeAction s r)
k (forall a. a -> Maybe a
Just (Int# -> Int
I# Int#
n#))
else Maybe Int -> ST s (DecodeAction s r)
k forall a. Maybe a
Nothing)))
{-# INLINE decodeMapLenOrIndef #-}
decodeBreakOr :: Decoder s Bool
decodeBreakOr :: forall s. Decoder s Bool
decodeBreakOr = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Bool -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Bool -> ST s (DecodeAction s a)) -> DecodeAction s a
ConsumeBreakOr (\Bool
b -> Bool -> ST s (DecodeAction s r)
k Bool
b)))
{-# INLINE decodeBreakOr #-}
peekTokenType :: Decoder s TokenType
peekTokenType :: forall s. Decoder s TokenType
peekTokenType = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\TokenType -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a.
(TokenType -> ST s (DecodeAction s a)) -> DecodeAction s a
PeekTokenType (\TokenType
tk -> TokenType -> ST s (DecodeAction s r)
k TokenType
tk)))
{-# INLINE peekTokenType #-}
peekAvailable :: Decoder s Int
peekAvailable :: forall s. Decoder s Int
peekAvailable = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
PeekAvailable (\Int#
len# -> Int -> ST s (DecodeAction s r)
k (Int# -> Int
I# Int#
len#))))
{-# INLINE peekAvailable #-}
type ByteOffset = Int64
peekByteOffset :: Decoder s ByteOffset
peekByteOffset :: forall s. Decoder s Int64
peekByteOffset = forall s a.
(forall r.
(a -> ST s (DecodeAction s r)) -> ST s (DecodeAction s r))
-> Decoder s a
Decoder (\Int64 -> ST s (DecodeAction s r)
k -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall s a. (Int# -> ST s (DecodeAction s a)) -> DecodeAction s a
PeekByteOffset (\Int#
off# -> Int64 -> ST s (DecodeAction s r)
k (Int# -> Int64
I64#
#if MIN_VERSION_base(4,17,0)
(intToInt64# off#)
#else
Int#
off#
#endif
))))
{-# INLINE peekByteOffset #-}
decodeWithByteSpan :: Decoder s a -> Decoder s (a, ByteOffset, ByteOffset)
decodeWithByteSpan :: forall s a. Decoder s a -> Decoder s (a, Int64, Int64)
decodeWithByteSpan Decoder s a
da = do
!Int64
before <- forall s. Decoder s Int64
peekByteOffset
a
x <- Decoder s a
da
!Int64
after <- forall s. Decoder s Int64
peekByteOffset
forall (m :: * -> *) a. Monad m => a -> m a
return (a
x, Int64
before, Int64
after)
decodeSequenceLenIndef :: (r -> a -> r)
-> r
-> (r -> r')
-> Decoder s a
-> Decoder s r'
decodeSequenceLenIndef :: forall r a r' s.
(r -> a -> r) -> r -> (r -> r') -> Decoder s a -> Decoder s r'
decodeSequenceLenIndef r -> a -> r
f r
z r -> r'
g Decoder s a
get =
r -> Decoder s r'
go r
z
where
go :: r -> Decoder s r'
go !r
acc = do
Bool
stop <- forall s. Decoder s Bool
decodeBreakOr
if Bool
stop then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! r -> r'
g r
acc
else do !a
x <- Decoder s a
get; r -> Decoder s r'
go (r -> a -> r
f r
acc a
x)
{-# INLINE decodeSequenceLenIndef #-}
decodeSequenceLenN :: (r -> a -> r)
-> r
-> (r -> r')
-> Int
-> Decoder s a
-> Decoder s r'
decodeSequenceLenN :: forall r a r' s.
(r -> a -> r)
-> r -> (r -> r') -> Int -> Decoder s a -> Decoder s r'
decodeSequenceLenN r -> a -> r
f r
z r -> r'
g Int
c Decoder s a
get =
forall {t}. (Eq t, Num t) => r -> t -> Decoder s r'
go r
z Int
c
where
go :: r -> t -> Decoder s r'
go !r
acc t
0 = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! r -> r'
g r
acc
go !r
acc t
n = do !a
x <- Decoder s a
get; r -> t -> Decoder s r'
go (r -> a -> r
f r
acc a
x) (t
nforall a. Num a => a -> a -> a
-t
1)
{-# INLINE decodeSequenceLenN #-}