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 | None |
Language | Haskell2010 |
High level API for decoding values that were encoded with the
Codec.CBOR.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))
- | 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))
- | 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))
- | 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))
- | 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))
- | Fail String
- | Done a
- liftST :: ST s a -> Decoder s 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
- decodeWordCanonical :: Decoder s Word
- decodeWord8Canonical :: Decoder s Word8
- decodeWord16Canonical :: Decoder s Word16
- decodeWord32Canonical :: Decoder s Word32
- decodeWord64Canonical :: Decoder s Word64
- decodeNegWordCanonical :: Decoder s Word
- decodeNegWord64Canonical :: Decoder s Word64
- decodeIntCanonical :: Decoder s Int
- decodeInt8Canonical :: Decoder s Int8
- decodeInt16Canonical :: Decoder s Int16
- decodeInt32Canonical :: Decoder s Int32
- decodeInt64Canonical :: Decoder s Int64
- decodeBytesCanonical :: Decoder s ByteString
- decodeByteArrayCanonical :: Decoder s ByteArray
- decodeStringCanonical :: Decoder s Text
- decodeUtf8ByteArrayCanonical :: Decoder s ByteArray
- decodeListLenCanonical :: Decoder s Int
- decodeMapLenCanonical :: Decoder s Int
- decodeTagCanonical :: Decoder s Word
- decodeTag64Canonical :: Decoder s Word64
- decodeIntegerCanonical :: Decoder s Integer
- decodeFloat16Canonical :: Decoder s Float
- decodeFloatCanonical :: Decoder s Float
- decodeDoubleCanonical :: Decoder s Double
- decodeSimpleCanonical :: Decoder s Word8
- decodeWordCanonicalOf :: Word -> Decoder s ()
- decodeListLenCanonicalOf :: Int -> Decoder s ()
- 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
has a Decoder
instance, you can easily
write Monad
s monadically for building your deserialisation
logic.Decoder
Since: cborg-0.2.0.0
data DecodeAction s a Source #
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
liftST :: ST s a -> Decoder s a Source #
Lift an ST
action into a Decoder
. Useful for, e.g., leveraging
in-place mutation to efficiently build a deserialised value.
Since: cborg-0.2.0.0
getDecodeAction :: Decoder s a -> ST s (DecodeAction s a) Source #
Given a
, give us the Decoder
DecodeAction
Since: cborg-0.2.0.0
Read input tokens
decodeBytes :: Decoder s ByteString Source #
Decode a string of bytes as a
.ByteString
Since: cborg-0.2.0.0
decodeBytesIndef :: Decoder s () Source #
Decode a token marking the beginning of an indefinite length set of bytes.
Since: cborg-0.2.0.0
decodeString :: Decoder s Text Source #
Decode a textual string as a piece of
.Text
Since: cborg-0.2.0.0
decodeStringIndef :: Decoder s () Source #
Decode a token marking the beginning of an indefinite length string.
Since: cborg-0.2.0.0
decodeListLen :: Decoder s Int Source #
Decode the length of a list.
Since: cborg-0.2.0.0
decodeListLenIndef :: Decoder s () Source #
Decode a token marking the beginning of a list of indefinite length.
Since: cborg-0.2.0.0
decodeMapLen :: Decoder s Int Source #
Decode the length of a map.
Since: cborg-0.2.0.0
decodeMapLenIndef :: Decoder s () Source #
Decode a token marking the beginning of a map of indefinite length.
Since: cborg-0.2.0.0
decodeTag :: Decoder s Word Source #
Decode an arbitrary tag and return it as a
.Word
Since: cborg-0.2.0.0
decodeTag64 :: Decoder s Word64 Source #
Decode an arbitrary 64-bit tag and return it as a
.Word64
Since: cborg-0.2.0.0
decodeBool :: Decoder s Bool Source #
Decode a bool.
Since: cborg-0.2.0.0
decodeNull :: Decoder s () Source #
Decode a nullary value, and return a unit value.
Since: cborg-0.2.0.0
decodeSimple :: Decoder s Word8 Source #
Decode a simple
CBOR value and give back a
. You
probably don't ever need to use this.Word8
Since: cborg-0.2.0.0
Specialised Read input token operations
Attempt to decode a word with
, and ensure the word
is exactly as expected, or fail.decodeWord
Since: cborg-0.2.0.0
decodeListLenOf :: Int -> Decoder s () Source #
Attempt to decode a list length using
, and
ensure it is exactly the specified length, or fail.decodeListLen
Since: cborg-0.2.0.0
Branching operations
decodeBreakOr :: Decoder s Bool Source #
Inspecting the token type
peekTokenType :: Decoder s TokenType Source #
Peek at the current token we're about to decode, and return a
specifying what it is.TokenType
Since: cborg-0.2.0.0
peekAvailable :: Decoder s Int Source #
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 Source # | |
Enum TokenType Source # | |
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] # | |
Eq TokenType Source # | |
Ord TokenType Source # | |
Defined in Codec.CBOR.Decoding | |
Show TokenType Source # | |
Canonical CBOR
https://tools.ietf.org/html/rfc7049#section-3.9
In general in CBOR there can be multiple representations for the same value,
for example the integer 0
represented in 8, 16, 32 or 64 bits. This
library always encodeds values in the shortest representation but on
decoding allows any valid encoding. For some applications it is useful or
important to only decode the canonical encoding. The decoder primitves here
are to allow applications to implement canonical decoding.
It is important to note that achieving a canonical representation is not
simply about using these primitives. For example consider a typical CBOR
encoding of a Haskell Set
data type. This will be encoded as a CBOR list
of the set elements. A typical implementation might be:
encodeSet = encodeList . Set.toList decodeSet = fmap Set.fromList . decodeList
This does not enforce a canonical encoding. The decoder above will allow
set elements in any order. The use of Set.fromList
forgets the order.
To enforce that the decoder only accepts the canonical encoding it will
have to check that the elemets in the list are strictly increasing.
Similar issues arise in many other data types, wherever there is redundancy
in the external representation.
The decoder primitives in this section are not much more expensive than their normal counterparts. If checking the canonical encoding property is critical then a technique that is more expensive but easier to implement and test is to decode normally, re-encode and check the serialised bytes are the same.
decodeWordCanonical :: Decoder s Word Source #
Decode canonical representation of a
.Word
Since: cborg-0.2.0.0
decodeWord8Canonical :: Decoder s Word8 Source #
Decode canonical representation of a
.Word8
Since: cborg-0.2.0.0
decodeWord16Canonical :: Decoder s Word16 Source #
Decode canonical representation of a
.Word16
Since: cborg-0.2.0.0
decodeWord32Canonical :: Decoder s Word32 Source #
Decode canonical representation of a
.Word32
Since: cborg-0.2.0.0
decodeWord64Canonical :: Decoder s Word64 Source #
Decode canonical representation of a
.Word64
Since: cborg-0.2.0.0
decodeNegWordCanonical :: Decoder s Word Source #
Decode canonical representation of a negative
.Word
Since: cborg-0.2.0.0
decodeNegWord64Canonical :: Decoder s Word64 Source #
Decode canonical representation of a negative
.Word64
Since: cborg-0.2.0.0
decodeIntCanonical :: Decoder s Int Source #
Decode canonical representation of an
.Int
Since: cborg-0.2.0.0
decodeInt8Canonical :: Decoder s Int8 Source #
Decode canonical representation of an
.Int8
Since: cborg-0.2.0.0
decodeInt16Canonical :: Decoder s Int16 Source #
Decode canonical representation of an
.Int16
Since: cborg-0.2.0.0
decodeInt32Canonical :: Decoder s Int32 Source #
Decode canonical representation of an
.Int32
Since: cborg-0.2.0.0
decodeInt64Canonical :: Decoder s Int64 Source #
Decode canonical representation of an
.Int64
Since: cborg-0.2.0.0
decodeBytesCanonical :: Decoder s ByteString Source #
Decode canonical representation of a string of bytes as a
.ByteString
Since: cborg-0.2.1.0
decodeStringCanonical :: Decoder s Text Source #
Decode canonical representation of a textual string as a piece of
.Text
Since: cborg-0.2.1.0
decodeUtf8ByteArrayCanonical :: Decoder s ByteArray Source #
Decode canonical representation of a textual string as UTF-8 encoded
ByteArray
. Note that the result is not validated to be well-formed UTF-8.
Also note that this will eagerly copy the content out of the input
to ensure that the input does not leak in the event that the ByteArray
is
live but not forced.
Since: cborg-0.2.1.0
decodeListLenCanonical :: Decoder s Int Source #
Decode canonical representation of the length of a list.
Since: cborg-0.2.0.0
decodeMapLenCanonical :: Decoder s Int Source #
Decode canonical representation of the length of a map.
Since: cborg-0.2.0.0
decodeTagCanonical :: Decoder s Word Source #
Decode canonical representation of an arbitrary tag and return it as a
.Word
Since: cborg-0.2.0.0
decodeTag64Canonical :: Decoder s Word64 Source #
Decode canonical representation of an arbitrary 64-bit tag and return it as
a
.Word64
Since: cborg-0.2.0.0
decodeIntegerCanonical :: Decoder s Integer Source #
Decode canonical representation of an
.Integer
Since: cborg-0.2.0.0
decodeFloat16Canonical :: Decoder s Float Source #
Decode canonical representation of a half-precision
.Float
Since: cborg-0.2.0.0
decodeFloatCanonical :: Decoder s Float Source #
Decode canonical representation of a
.Float
Since: cborg-0.2.0.0
decodeDoubleCanonical :: Decoder s Double Source #
Decode canonical representation of a
.Double
Since: cborg-0.2.0.0
decodeSimpleCanonical :: Decoder s Word8 Source #
Decode canonical representation of a simple
CBOR value and give back a
. You probably don't ever need to use this.Word8
Since: cborg-0.2.0.0
decodeWordCanonicalOf Source #
Attempt to decode canonical representation of a word with
,
and ensure the word is exactly as expected, or fail.decodeWordCanonical
Since: cborg-0.2.0.0
decodeListLenCanonicalOf :: Int -> Decoder s () Source #
Attempt to decode canonical representation of a list length using
, and ensure it is exactly the specified length, or
fail.decodeListLenCanonical
Since: cborg-0.2.0.0
Sequence operations
decodeSequenceLenIndef :: (r -> a -> r) -> r -> (r -> r') -> Decoder s a -> Decoder s r' Source #
Decode an indefinite sequence length.
Since: cborg-0.2.0.0