cereal-0.1: A binary serialization library

StabilityPortability :
MaintainerTrevor Elliott <trevor@galois.com>

Data.Serialize.Get

Contents

Description

The Get monad. A monad for efficiently building structures from strict ByteStrings

Synopsis

The Get type

data Get a Source

The Get monad is an Exception and State monad.

runGet :: Get a -> ByteString -> Either String aSource

Run the Get monad applies a get-based parser on the input ByteString

runGetState :: Get a -> ByteString -> Int -> Either String (a, ByteString)Source

Run the Get monad applies a get-based parser on the input ByteString. Additional to the result of get it returns the number of consumed bytes and the rest of the input.

Parsing

isolate :: String -> Int -> Get a -> Get aSource

Isolate an action to operating within a fixed block of bytes. The action is required to consume all the bytes that it is isolated to.

skip :: Int -> Get ()Source

Skip ahead n bytes. Fails if fewer than n bytes are available.

uncheckedSkip :: Int -> Get ()Source

Skip ahead n bytes. No error if there isn't enough bytes.

lookAhead :: Get a -> Get aSource

Run ga, but return without consuming its input. Fails if ga fails.

lookAheadM :: Get (Maybe a) -> Get (Maybe a)Source

Like lookAhead, but consume the input if gma returns 'Just _'. Fails if gma fails.

lookAheadE :: Get (Either a b) -> Get (Either a b)Source

Like lookAhead, but consume the input if gea returns 'Right _'. Fails if gea fails.

uncheckedLookAhead :: Int -> Get ByteStringSource

Get the next up to n bytes as a ByteString, without consuming them.

Utility

getBytes :: Int -> Get ByteStringSource

Pull n bytes from the input, as a strict ByteString.

remaining :: Get IntSource

Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed. Note that this forces the rest of the input.

isEmpty :: Get BoolSource

Test whether all input has been consumed, i.e. there are no remaining unparsed bytes.

Parsing particular types

getWord8 :: Get Word8Source

Read a Word8 from the monad state

ByteStrings

getByteString :: Int -> Get ByteStringSource

An efficient get method for strict ByteStrings. Fails if fewer than n bytes are left in the input.

Big-endian reads

getWord16be :: Get Word16Source

Read a Word16 in big endian format

getWord32be :: Get Word32Source

Read a Word32 in big endian format

getWord64be :: Get Word64Source

Read a Word64 in big endian format

Little-endian reads

getWord16le :: Get Word16Source

Read a Word16 in little endian format

getWord32le :: Get Word32Source

Read a Word32 in little endian format

getWord64le :: Get Word64Source

Read a Word64 in little endian format

Host-endian, unaligned reads

getWordhost :: Get WordSource

O(1). Read a single native machine word. The word is read in host order, host endian form, for the machine you're on. On a 64 bit machine the Word is an 8 byte value, on a 32 bit machine, 4 bytes.

getWord16host :: Get Word16Source

O(1). Read a 2 byte Word16 in native host order and host endianness.

getWord32host :: Get Word32Source

O(1). Read a Word32 in native host order and host endianness.

getWord64host :: Get Word64Source

O(1). Read a Word64 in native host order and host endianess.

Containers

getTwoOf :: Get a -> Get b -> Get (a, b)Source

getListOf :: Get a -> Get [a]Source

Get a list in the following format: Word64 (big endian format) element 1 ... element n

getIArrayOf :: (Ix i, IArray a e) => Get i -> Get e -> Get (a i e)Source

Get an IArray in the following format: index (lower bound) index (upper bound) Word64 (big endian format) element 1 ... element n

getTreeOf :: Get a -> Get (Tree a)Source

Read as a list of lists.

getSeqOf :: Get a -> Get (Seq a)Source

Get a sequence in the following format: Word64 (big endian format) element 1 ... element n

getMapOf :: Ord k => Get k -> Get a -> Get (Map k a)Source

Read as a list of pairs of key and element.

getIntMapOf :: Get Int -> Get a -> Get (IntMap a)Source

Read as a list of pairs of int and element.

getSetOf :: Ord a => Get a -> Get (Set a)Source

Read as a list of elements.

getIntSetOf :: Get Int -> Get IntSetSource

Read as a list of ints.

getMaybeOf :: Get a -> Get (Maybe a)Source

Read in a Maybe in the following format: Word8 (0 for Nothing, anything else for Just) element (when Just)

getEitherOf :: Get a -> Get b -> Get (Either a b)Source

Read an Either, in the following format: Word8 (0 for Left, anything else for Right) element a when 0, element b otherwise