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
A continuation-based decoder, used for decoding values that were
previously encoded using the Codec.CBOR.Encoding
module. As Decoder
has a Monad
instance, you can easily
write Decoder
s monadically for building your deserialisation
logic.
Since: cborg-0.2.0.0
Instances
MonadFail (Decoder s) | Since: cborg-0.2.0.0 |
Defined in Codec.CBOR.Decoding | |
Applicative (Decoder s) | Since: cborg-0.2.0.0 |
Functor (Decoder s) | Since: cborg-0.2.0.0 |
Monad (Decoder s) | Since: cborg-0.2.0.0 |
data DecodeAction s a #
An action, representing a step for a decoder to taken and a continuation to invoke with the expected value.
Since: cborg-0.2.0.0
getDecodeAction :: Decoder s a -> ST s (DecodeAction s a) #
Given a Decoder
, give us the DecodeAction
Since: cborg-0.2.0.0
Read input tokens
decodeWord :: Decoder s Word #
Decode a Word
.
Since: cborg-0.2.0.0
decodeWord8 :: Decoder s Word8 #
Decode a Word8
.
Since: cborg-0.2.0.0
decodeWord16 :: Decoder s Word16 #
Decode a Word16
.
Since: cborg-0.2.0.0
decodeWord32 :: Decoder s Word32 #
Decode a Word32
.
Since: cborg-0.2.0.0
decodeWord64 :: Decoder s Word64 #
Decode a Word64
.
Since: cborg-0.2.0.0
decodeNegWord :: Decoder s Word #
Decode a negative Word
.
Since: cborg-0.2.0.0
decodeNegWord64 :: Decoder s Word64 #
Decode a negative Word64
.
Since: cborg-0.2.0.0
decodeInt8 :: Decoder s Int8 #
Decode an Int8
.
Since: cborg-0.2.0.0
decodeInt16 :: Decoder s Int16 #
Decode an Int16
.
Since: cborg-0.2.0.0
decodeInt32 :: Decoder s Int32 #
Decode an Int32
.
Since: cborg-0.2.0.0
decodeInt64 :: Decoder s Int64 #
Decode an Int64
.
Since: cborg-0.2.0.0
decodeInteger :: Decoder s Integer #
Decode an Integer
.
Since: cborg-0.2.0.0
decodeFloat :: Decoder s Float #
Decode a Float
.
Since: cborg-0.2.0.0
decodeDouble :: Decoder s Double #
Decode a Double
.
Since: cborg-0.2.0.0
decodeBytes :: Decoder s ByteString #
Decode a string of bytes as a ByteString
.
Since: cborg-0.2.0.0
decodeBytesIndef :: Decoder s () #
Decode a token marking the beginning of an indefinite length set of bytes.
Since: cborg-0.2.0.0
decodeByteArray :: Decoder s ByteArray #
decodeString :: Decoder s Text #
Decode a textual string as a piece of Text
.
Since: cborg-0.2.0.0
decodeStringIndef :: Decoder s () #
Decode a token marking the beginning of an indefinite length string.
Since: cborg-0.2.0.0
decodeListLen :: Decoder s Int #
Decode the length of a list.
Since: cborg-0.2.0.0
decodeListLenIndef :: Decoder s () #
Decode a token marking the beginning of a list of indefinite length.
Since: cborg-0.2.0.0
decodeMapLen :: Decoder s Int #
Decode the length of a map.
Since: cborg-0.2.0.0
decodeMapLenIndef :: Decoder s () #
Decode a token marking the beginning of a map of indefinite length.
Since: cborg-0.2.0.0
decodeTag64 :: Decoder s Word64 #
Decode an arbitrary 64-bit tag and return it as a Word64
.
Since: cborg-0.2.0.0
decodeBool :: Decoder s Bool #
Decode a bool.
Since: cborg-0.2.0.0
decodeNull :: Decoder s () #
Decode a nullary value, and return a unit value.
Since: cborg-0.2.0.0
decodeSimple :: Decoder s Word8 #
Decode a simple
CBOR value and give back a Word8
. You
probably don't ever need to use this.
Since: cborg-0.2.0.0
Specialised Read input token operations
Attempt to decode a word with decodeWord
, and ensure the word
is exactly as expected, or fail.
Since: cborg-0.2.0.0
decodeListLenOf :: Int -> Decoder s () #
Attempt to decode a list length using decodeListLen
, and
ensure it is exactly the specified length, or fail.
Since: cborg-0.2.0.0
Branching operations
decodeListLenOrIndef :: Decoder s (Maybe Int) #
decodeMapLenOrIndef :: Decoder s (Maybe Int) #
decodeBreakOr :: Decoder s Bool #
Inspecting the token type
peekTokenType :: Decoder s TokenType #
Peek at the current token we're about to decode, and return a
TokenType
specifying what it is.
Since: cborg-0.2.0.0
peekAvailable :: Decoder s Int #
Peek and return the length of the current buffer that we're running our decoder on.
Since: cborg-0.2.0.0
The type of a token, which a decoder can ask for at an arbitrary time.
Since: cborg-0.2.0.0
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' #
Decode an indefinite sequence length.
Since: cborg-0.2.0.0
decodeSequenceLenN :: (r -> a -> r) -> r -> (r -> r') -> Int -> Decoder s a -> Decoder s r' #
Decode a sequence length.
Since: cborg-0.2.0.0