cereal-0.5.3.0: A binary serialization library

CopyrightLennart Kolmodin, Galois Inc. 2009
LicenseBSD3-style (see LICENSE)
MaintainerTrevor Elliott <trevor@galois.com>
StabilityPortability :
Safe HaskellNone
LanguageHaskell2010

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.

Instances

Monad Get Source # 

Methods

(>>=) :: Get a -> (a -> Get b) -> Get b #

(>>) :: Get a -> Get b -> Get b #

return :: a -> Get a #

fail :: String -> Get a #

Functor Get Source # 

Methods

fmap :: (a -> b) -> Get a -> Get b #

(<$) :: a -> Get b -> Get a #

MonadFail Get Source # 

Methods

fail :: String -> Get a #

Applicative Get Source # 

Methods

pure :: a -> Get a #

(<*>) :: Get (a -> b) -> Get a -> Get b #

(*>) :: Get a -> Get b -> Get b #

(<*) :: Get a -> Get b -> Get a #

Alternative Get Source # 

Methods

empty :: Get a #

(<|>) :: Get a -> Get a -> Get a #

some :: Get a -> Get [a] #

many :: Get a -> Get [a] #

MonadPlus Get Source # 

Methods

mzero :: Get a #

mplus :: Get a -> Get a -> Get a #

runGet :: Get a -> ByteString -> Either String a Source #

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

runGetLazy :: Get a -> ByteString -> Either String a Source #

Run the Get monad over a Lazy ByteString. Note that this will not run the Get parser lazily, but will operate on lazy ByteStrings.

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.

runGetLazyState :: Get a -> ByteString -> Either String (a, ByteString) Source #

Run the Get monad over a Lazy ByteString. Note that this does not run the Get parser lazily, but will operate on lazy ByteStrings.

Incremental interface

data Result r Source #

The result of a parse.

Constructors

Fail String ByteString

The parse failed. The String is the message describing the error, if any.

Partial (ByteString -> Result r)

Supply this continuation with more input so that the parser can resume. To indicate that no more input is available, use an empty string.

Done r ByteString

The parse succeeded. The ByteString is the input that had not yet been consumed (if any) when the parse succeeded.

Instances

Functor Result Source # 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Show r => Show (Result r) Source # 

Methods

showsPrec :: Int -> Result r -> ShowS #

show :: Result r -> String #

showList :: [Result r] -> ShowS #

runGetPartial :: Get a -> ByteString -> Result a Source #

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

runGetChunk :: Get a -> Maybe Int -> ByteString -> Result a Source #

Run the get monad on a single chunk, providing an optional length for the remaining, unseen input, with Nothing indicating that it's not clear how much input is left. For example, with a lazy ByteString, the optional length represents the sum of the lengths of all remaining chunks.

Parsing

ensure :: Int -> Get ByteString Source #

If at least n bytes of input are available, return the current input, otherwise fail.

isolate :: Int -> Get a -> Get a Source #

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.

label :: String -> Get a -> Get a Source #

skip :: Int -> Get () Source #

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

uncheckedSkip :: Int -> Get () Source #

Skip ahead up to n bytes in the current chunk. No error if there aren't enough bytes, or if less than n bytes are skipped.

lookAhead :: Get a -> Get a Source #

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 ByteString Source #

Get the next up to n bytes as a ByteString until end of this chunk, without consuming them.

Utility

getBytes :: Int -> Get ByteString Source #

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

remaining :: Get Int Source #

Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed.

WARNING: when run with runGetPartial, remaining will only return the number of bytes that are remaining in the current input.

isEmpty :: Get Bool Source #

Test whether all input has been consumed.

WARNING: when run with runGetPartial, isEmpty will only tell you if you're at the end of the current chunk.

Parsing particular types

getWord8 :: Get Word8 Source #

Read a Word8 from the monad state

getInt8 :: Get Int8 Source #

Read a Int8 from the monad state

ByteStrings

getByteString :: Int -> Get ByteString Source #

An efficient get method for strict ByteStrings. Fails if fewer than n bytes are left in the input. This function creates a fresh copy of the underlying bytes.

Big-endian reads

getWord16be :: Get Word16 Source #

Read a Word16 in big endian format

getWord32be :: Get Word32 Source #

Read a Word32 in big endian format

getWord64be :: Get Word64 Source #

Read a Word64 in big endian format

getInt16be :: Get Int16 Source #

Read a Int16 in big endian format

getInt32be :: Get Int32 Source #

Read a Int32 in big endian format

getInt64be :: Get Int64 Source #

Read a Int64 in big endian format

Little-endian reads

getWord16le :: Get Word16 Source #

Read a Word16 in little endian format

getWord32le :: Get Word32 Source #

Read a Word32 in little endian format

getWord64le :: Get Word64 Source #

Read a Word64 in little endian format

getInt16le :: Get Int16 Source #

Read a Int16 in little endian format

getInt32le :: Get Int32 Source #

Read a Int32 in little endian format

getInt64le :: Get Int64 Source #

Read a Int64 in little endian format

Host-endian, unaligned reads

getWordhost :: Get Word Source #

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 Word16 Source #

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

getWord32host :: Get Word32 Source #

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

getWord64host :: Get Word64 Source #

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 IntSet Source #

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

getNested :: Get Int -> Get a -> Get a Source #

Read in a length and then read a nested structure of that length.