Copyright | (c) Duncan Coutts 2015-2017 |
---|---|
License | BSD3-style (see LICENSE.txt) |
Maintainer | duncan@community.haskell.org |
Stability | experimental |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
High level API for decoding values that were encoded with the
Codec.Serialise.Encoding module, using a
based interface.Monad
Synopsis
- data Decoder s a
- 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))
- | 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))
- | ConsumeNull (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))
- | PeekByteOffset (Int# -> ST s (DecodeAction s a))
- | 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))
- | 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
- getDecodeAction :: Decoder s a -> ST s (DecodeAction s a)
- decodeWord :: Decoder s Word
- decodeWord8 :: Decoder s Word8
- decodeWord16 :: Decoder s Word16
- decodeWord32 :: Decoder s Word32
- decodeWord64 :: Decoder s Word64
- decodeNegWord :: Decoder s Word
- decodeNegWord64 :: Decoder s Word64
- decodeInt :: Decoder s Int
- decodeInt8 :: Decoder s Int8
- decodeInt16 :: Decoder s Int16
- decodeInt32 :: Decoder s Int32
- decodeInt64 :: Decoder s Int64
- decodeInteger :: Decoder s Integer
- decodeFloat :: Decoder s Float
- decodeDouble :: Decoder s Double
- decodeBytes :: Decoder s ByteString
- decodeBytesIndef :: Decoder s ()
- decodeByteArray :: Decoder s ByteArray
- decodeString :: Decoder s Text
- decodeStringIndef :: Decoder s ()
- decodeUtf8ByteArray :: Decoder s ByteArray
- decodeListLen :: Decoder s Int
- decodeListLenIndef :: Decoder s ()
- decodeMapLen :: Decoder s Int
- decodeMapLenIndef :: Decoder s ()
- decodeTag :: Decoder s Word
- decodeTag64 :: Decoder s Word64
- decodeBool :: Decoder s Bool
- decodeNull :: Decoder s ()
- decodeSimple :: Decoder s Word8
- decodeWordOf :: Word -> Decoder s ()
- decodeListLenOf :: Int -> Decoder s ()
- decodeListLenOrIndef :: Decoder s (Maybe Int)
- decodeMapLenOrIndef :: Decoder s (Maybe Int)
- decodeBreakOr :: Decoder s Bool
- peekTokenType :: Decoder s TokenType
- peekAvailable :: Decoder s Int
- 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
- decodeSequenceLenIndef :: (r -> a -> r) -> r -> (r -> r') -> Decoder s a -> Decoder s r'
- decodeSequenceLenN :: (r -> a -> r) -> r -> (r -> r') -> Int -> Decoder s a -> Decoder s r'
Decode primitive operations
Instances
MonadFail (Decoder s) | |
Defined in Codec.CBOR.Decoding | |
Applicative (Decoder s) | |
Functor (Decoder s) | |
Monad (Decoder s) | |
data DecodeAction s a #
getDecodeAction :: Decoder s a -> ST s (DecodeAction s a) #
Read input tokens
decodeWord :: Decoder s Word #
decodeWord8 :: Decoder s Word8 #
decodeWord16 :: Decoder s Word16 #
decodeWord32 :: Decoder s Word32 #
decodeWord64 :: Decoder s Word64 #
decodeNegWord :: Decoder s Word #
decodeNegWord64 :: Decoder s Word64 #
decodeInt8 :: Decoder s Int8 #
decodeInt16 :: Decoder s Int16 #
decodeInt32 :: Decoder s Int32 #
decodeInt64 :: Decoder s Int64 #
decodeInteger :: Decoder s Integer #
decodeFloat :: Decoder s Float #
decodeDouble :: Decoder s Double #
decodeBytes :: Decoder s ByteString #
decodeBytesIndef :: Decoder s () #
decodeByteArray :: Decoder s ByteArray #
decodeString :: Decoder s Text #
decodeStringIndef :: Decoder s () #
decodeUtf8ByteArray :: Decoder s ByteArray #
decodeListLen :: Decoder s Int #
decodeListLenIndef :: Decoder s () #
decodeMapLen :: Decoder s Int #
decodeMapLenIndef :: Decoder s () #
decodeTag64 :: Decoder s Word64 #
decodeBool :: Decoder s Bool #
decodeNull :: Decoder s () #
decodeSimple :: Decoder s Word8 #
Specialised Read input token operations
decodeWordOf :: Word -> Decoder s () #
decodeListLenOf :: Int -> Decoder s () #
Branching operations
decodeListLenOrIndef :: Decoder s (Maybe Int) #
decodeMapLenOrIndef :: Decoder s (Maybe Int) #
decodeBreakOr :: Decoder s Bool #
Inspecting the token type
peekTokenType :: Decoder s TokenType #
peekAvailable :: Decoder s Int #
Instances
Bounded TokenType | |
Enum TokenType | |
Defined in Codec.CBOR.Decoding succ :: TokenType -> TokenType # pred :: TokenType -> TokenType # fromEnum :: TokenType -> Int # enumFrom :: TokenType -> [TokenType] # enumFromThen :: TokenType -> TokenType -> [TokenType] # enumFromTo :: TokenType -> TokenType -> [TokenType] # enumFromThenTo :: TokenType -> TokenType -> TokenType -> [TokenType] # | |
Show TokenType | |
Eq TokenType | |
Ord TokenType | |
Defined in Codec.CBOR.Decoding |
Special operations
Sequence operations
decodeSequenceLenIndef :: (r -> a -> r) -> r -> (r -> r') -> Decoder s a -> Decoder s r' #
decodeSequenceLenN :: (r -> a -> r) -> r -> (r -> r') -> Int -> Decoder s a -> Decoder s r' #