serialise-0.2.1.0: A binary serialisation library for Haskell values.

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

Codec.Serialise.Decoding

Contents

Description

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

Synopsis

Decode primitive operations

data Decoder s a #

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

Instances
Monad (Decoder s)

Since: cborg-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)

Since: cborg-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)

Since: cborg-0.2.0.0

Instance details

Defined in Codec.CBOR.Decoding

Methods

fail :: String -> Decoder s a #

Applicative (Decoder s)

Since: cborg-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 #

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

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)) 
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 

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

decodeInt :: Decoder s Int #

Decode an Int.

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 #

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

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

decodeUtf8ByteArray :: Decoder s ByteArray #

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

decodeTag :: Decoder s Word #

Decode an arbitrary tag and return it as a Word.

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

decodeWordOf #

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: 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) #

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

decodeMapLenOrIndef :: Decoder s (Maybe Int) #

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

decodeBreakOr :: Decoder s Bool #

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

Since: cborg-0.2.0.0

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

data TokenType #

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

Since: cborg-0.2.0.0

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