cborg-0.2.2.0: Concise Binary Object Representation (CBOR)

Copyright(c) Duncan Coutts 2015-2017
LicenseBSD3-style (see LICENSE.txt)
Maintainerduncan@community.haskell.org
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Codec.CBOR.Decoding

Contents

Description

High level API for decoding values that were encoded with the Codec.CBOR.Encoding module, using a Monad based interface.

Synopsis

Decode primitive operations

data Decoder s a Source #

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 Decoders monadically for building your deserialisation logic.

Since: 0.2.0.0

Instances
Monad (Decoder s) Source #

Since: 0.2.0.0

Instance details

Defined in Codec.CBOR.Decoding

Methods

(>>=) :: Decoder s a -> (a -> Decoder s b) -> Decoder s b #

(>>) :: Decoder s a -> Decoder s b -> Decoder s b #

return :: a -> Decoder s a #

fail :: String -> Decoder s a #

Functor (Decoder s) Source #

Since: 0.2.0.0

Instance details

Defined in Codec.CBOR.Decoding

Methods

fmap :: (a -> b) -> Decoder s a -> Decoder s b #

(<$) :: a -> Decoder s b -> Decoder s a #

MonadFail (Decoder s) Source #

Since: 0.2.0.0

Instance details

Defined in Codec.CBOR.Decoding

Methods

fail :: String -> Decoder s a #

Applicative (Decoder s) Source #

Since: 0.2.0.0

Instance details

Defined in Codec.CBOR.Decoding

Methods

pure :: a -> Decoder s a #

(<*>) :: Decoder s (a -> b) -> Decoder s a -> Decoder s b #

liftA2 :: (a -> b -> c) -> Decoder s a -> Decoder s b -> Decoder s c #

(*>) :: Decoder s a -> Decoder s b -> Decoder s b #

(<*) :: Decoder s a -> Decoder s b -> Decoder s a #

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: 0.2.0.0

Constructors

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 

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: 0.2.0.0

getDecodeAction :: Decoder s a -> ST s (DecodeAction s a) Source #

Given a Decoder, give us the DecodeAction

Since: 0.2.0.0

Read input tokens

decodeWord :: Decoder s Word Source #

Decode a Word.

Since: 0.2.0.0

decodeWord8 :: Decoder s Word8 Source #

Decode a Word8.

Since: 0.2.0.0

decodeWord16 :: Decoder s Word16 Source #

Decode a Word16.

Since: 0.2.0.0

decodeWord32 :: Decoder s Word32 Source #

Decode a Word32.

Since: 0.2.0.0

decodeWord64 :: Decoder s Word64 Source #

Decode a Word64.

Since: 0.2.0.0

decodeNegWord :: Decoder s Word Source #

Decode a negative Word.

Since: 0.2.0.0

decodeNegWord64 :: Decoder s Word64 Source #

Decode a negative Word64.

Since: 0.2.0.0

decodeInt :: Decoder s Int Source #

Decode an Int.

Since: 0.2.0.0

decodeInt8 :: Decoder s Int8 Source #

Decode an Int8.

Since: 0.2.0.0

decodeInt16 :: Decoder s Int16 Source #

Decode an Int16.

Since: 0.2.0.0

decodeInt32 :: Decoder s Int32 Source #

Decode an Int32.

Since: 0.2.0.0

decodeInt64 :: Decoder s Int64 Source #

Decode an Int64.

Since: 0.2.0.0

decodeInteger :: Decoder s Integer Source #

Decode an Integer.

Since: 0.2.0.0

decodeFloat :: Decoder s Float Source #

Decode a Float.

Since: 0.2.0.0

decodeDouble :: Decoder s Double Source #

Decode a Double.

Since: 0.2.0.0

decodeBytes :: Decoder s ByteString Source #

Decode a string of bytes as a ByteString.

Since: 0.2.0.0

decodeBytesIndef :: Decoder s () Source #

Decode a token marking the beginning of an indefinite length set of bytes.

Since: 0.2.0.0

decodeByteArray :: Decoder s ByteArray Source #

Decode a string of bytes as a ByteArray.

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: 0.2.0.0

decodeString :: Decoder s Text Source #

Decode a textual string as a piece of Text.

Since: 0.2.0.0

decodeStringIndef :: Decoder s () Source #

Decode a token marking the beginning of an indefinite length string.

Since: 0.2.0.0

decodeUtf8ByteArray :: Decoder s ByteArray Source #

Decode 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: 0.2.0.0

decodeListLen :: Decoder s Int Source #

Decode the length of a list.

Since: 0.2.0.0

decodeListLenIndef :: Decoder s () Source #

Decode a token marking the beginning of a list of indefinite length.

Since: 0.2.0.0

decodeMapLen :: Decoder s Int Source #

Decode the length of a map.

Since: 0.2.0.0

decodeMapLenIndef :: Decoder s () Source #

Decode a token marking the beginning of a map of indefinite length.

Since: 0.2.0.0

decodeTag :: Decoder s Word Source #

Decode an arbitrary tag and return it as a Word.

Since: 0.2.0.0

decodeTag64 :: Decoder s Word64 Source #

Decode an arbitrary 64-bit tag and return it as a Word64.

Since: 0.2.0.0

decodeBool :: Decoder s Bool Source #

Decode a bool.

Since: 0.2.0.0

decodeNull :: Decoder s () Source #

Decode a nullary value, and return a unit value.

Since: 0.2.0.0

decodeSimple :: Decoder s Word8 Source #

Decode a simple CBOR value and give back a Word8. You probably don't ever need to use this.

Since: 0.2.0.0

Specialised Read input token operations

decodeWordOf Source #

Arguments

:: Word

Expected value of the decoded word

-> Decoder s () 

Attempt to decode a word with decodeWord, and ensure the word is exactly as expected, or fail.

Since: 0.2.0.0

decodeListLenOf :: Int -> Decoder s () Source #

Attempt to decode a list length using decodeListLen, and ensure it is exactly the specified length, or fail.

Since: 0.2.0.0

Branching operations

decodeListLenOrIndef :: Decoder s (Maybe Int) Source #

Attempt to decode a token for the length of a finite, known list, or an indefinite list. If Nothing is returned, then an indefinite length list occurs afterwords. If Just x is returned, then a list of length x is encoded.

Since: 0.2.0.0

decodeMapLenOrIndef :: Decoder s (Maybe Int) Source #

Attempt to decode a token for the length of a finite, known map, or an indefinite map. If Nothing is returned, then an indefinite length map occurs afterwords. If Just x is returned, then a map of length x is encoded.

Since: 0.2.0.0

decodeBreakOr :: Decoder s Bool Source #

Attempt to decode a Break token, and if that was successful, return True. If the token was of any other type, return False.

Since: 0.2.0.0

Inspecting the token type

peekTokenType :: Decoder s TokenType Source #

Peek at the current token we're about to decode, and return a TokenType specifying what it is.

Since: 0.2.0.0

data TokenType Source #

The type of a token, which a decoder can ask for at an arbitrary time.

Since: 0.2.0.0

Special operations

peekAvailable :: Decoder s Int Source #

Peek and return the length of the current buffer that we're running our decoder on.

Since: 0.2.0.0

type ByteOffset = Int64 Source #

A 0-based offset within the overall byte sequence that makes up the input to the Decoder.

This is an Int64 since Decoder is incremental and can decode more data than fits in memory at once. This is also compatible with the result type of length.

peekByteOffset :: Decoder s ByteOffset Source #

Get the current ByteOffset in the input byte sequence of the Decoder.

The Decoder does not provide any facility to get at the input data directly (since that is tricky with an incremental decoder). The next best is this primitive which can be used to keep track of the offset within the input bytes that makes up the encoded form of a term.

By keeping track of the byte offsets before and after decoding a subterm (a pattern captured by decodeWithByteSpan) and if the overall input data is retained then this is enables later retrieving the span of bytes for the subterm.

Since: 0.2.2.0

decodeWithByteSpan :: Decoder s a -> Decoder s (a, ByteOffset, ByteOffset) Source #

This captures the pattern of getting the byte offsets before and after decoding a subterm.

!before <- peekByteOffset
x <- decode
!after  <- peekByteOffset

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 can be represented in 8, 16, 32 or 64 bits. This library always encoded 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 primitives 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 elements 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: 0.2.0.0

decodeWord8Canonical :: Decoder s Word8 Source #

Decode canonical representation of a Word8.

Since: 0.2.0.0

decodeWord16Canonical :: Decoder s Word16 Source #

Decode canonical representation of a Word16.

Since: 0.2.0.0

decodeWord32Canonical :: Decoder s Word32 Source #

Decode canonical representation of a Word32.

Since: 0.2.0.0

decodeWord64Canonical :: Decoder s Word64 Source #

Decode canonical representation of a Word64.

Since: 0.2.0.0

decodeNegWordCanonical :: Decoder s Word Source #

Decode canonical representation of a negative Word.

Since: 0.2.0.0

decodeNegWord64Canonical :: Decoder s Word64 Source #

Decode canonical representation of a negative Word64.

Since: 0.2.0.0

decodeIntCanonical :: Decoder s Int Source #

Decode canonical representation of an Int.

Since: 0.2.0.0

decodeInt8Canonical :: Decoder s Int8 Source #

Decode canonical representation of an Int8.

Since: 0.2.0.0

decodeInt16Canonical :: Decoder s Int16 Source #

Decode canonical representation of an Int16.

Since: 0.2.0.0

decodeInt32Canonical :: Decoder s Int32 Source #

Decode canonical representation of an Int32.

Since: 0.2.0.0

decodeInt64Canonical :: Decoder s Int64 Source #

Decode canonical representation of an Int64.

Since: 0.2.0.0

decodeBytesCanonical :: Decoder s ByteString Source #

Decode canonical representation of a string of bytes as a ByteString.

Since: 0.2.1.0

decodeByteArrayCanonical :: Decoder s ByteArray Source #

Decode canonical representation of a string of bytes as a ByteArray.

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: 0.2.1.0

decodeStringCanonical :: Decoder s Text Source #

Decode canonical representation of a textual string as a piece of Text.

Since: 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: 0.2.1.0

decodeListLenCanonical :: Decoder s Int Source #

Decode canonical representation of the length of a list.

Since: 0.2.0.0

decodeMapLenCanonical :: Decoder s Int Source #

Decode canonical representation of the length of a map.

Since: 0.2.0.0

decodeTagCanonical :: Decoder s Word Source #

Decode canonical representation of an arbitrary tag and return it as a Word.

Since: 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: 0.2.0.0

decodeIntegerCanonical :: Decoder s Integer Source #

Decode canonical representation of an Integer.

Since: 0.2.0.0

decodeFloat16Canonical :: Decoder s Float Source #

Decode canonical representation of a half-precision Float.

Since: 0.2.0.0

decodeFloatCanonical :: Decoder s Float Source #

Decode canonical representation of a Float.

Since: 0.2.0.0

decodeDoubleCanonical :: Decoder s Double Source #

Decode canonical representation of a Double.

Since: 0.2.0.0

decodeSimpleCanonical :: Decoder s Word8 Source #

Decode canonical representation of a simple CBOR value and give back a Word8. You probably don't ever need to use this.

Since: 0.2.0.0

decodeWordCanonicalOf Source #

Arguments

:: Word

Expected value of the decoded word

-> Decoder s () 

Attempt to decode canonical representation of a word with decodeWordCanonical, and ensure the word is exactly as expected, or fail.

Since: 0.2.0.0

decodeListLenCanonicalOf :: Int -> Decoder s () Source #

Attempt to decode canonical representation of a list length using decodeListLenCanonical, and ensure it is exactly the specified length, or fail.

Since: 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: 0.2.0.0

decodeSequenceLenN :: (r -> a -> r) -> r -> (r -> r') -> Int -> Decoder s a -> Decoder s r' Source #

Decode a sequence length.

Since: 0.2.0.0