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 HaskellSafe
LanguageHaskell2010

Data.Serialize.Put

Contents

Description

The Put monad. A monad for efficiently constructing bytestrings.

Synopsis

The Put type

type Put = PutM () Source #

Put merely lifts Builder into a Writer monad, applied to ().

newtype PutM a Source #

The PutM type. A Writer monad over the efficient Builder monoid.

Constructors

Put 

Fields

Instances

Monad PutM Source # 

Methods

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

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

return :: a -> PutM a #

fail :: String -> PutM a #

Functor PutM Source # 

Methods

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

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

Applicative PutM Source # 

Methods

pure :: a -> PutM a #

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

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

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

Monoid (PutM ()) Source # 

Methods

mempty :: PutM () #

mappend :: PutM () -> PutM () -> PutM () #

mconcat :: [PutM ()] -> PutM () #

type Putter a = a -> Put Source #

runPut :: Put -> ByteString Source #

Run the Put monad with a serialiser

runPutM :: PutM a -> (a, ByteString) Source #

Run the Put monad with a serialiser and get its result

runPutLazy :: Put -> ByteString Source #

Run the Put monad with a serialiser

runPutMLazy :: PutM a -> (a, ByteString) Source #

Run the Put monad with a serialiser

execPut :: PutM a -> Builder Source #

Run the Put monad

Flushing the implicit parse state

flush :: Put Source #

Pop the ByteString we have constructed so far, if any, yielding a new chunk in the result ByteString.

Primitives

putWord8 :: Putter Word8 Source #

Efficiently write a byte into the output buffer

putByteString :: Putter ByteString Source #

An efficient primitive to write a strict ByteString into the output buffer. It flushes the current buffer, and writes the argument into a new chunk.

putLazyByteString :: Putter ByteString Source #

Write a lazy ByteString efficiently, simply appending the lazy ByteString chunks to the output buffer

Big-endian primitives

putWord16be :: Putter Word16 Source #

Write a Word16 in big endian format

putWord32be :: Putter Word32 Source #

Write a Word32 in big endian format

putWord64be :: Putter Word64 Source #

Write a Word64 in big endian format

Little-endian primitives

putWord16le :: Putter Word16 Source #

Write a Word16 in little endian format

putWord32le :: Putter Word32 Source #

Write a Word32 in little endian format

putWord64le :: Putter Word64 Source #

Write a Word64 in little endian format

Host-endian, unaligned writes

putWordhost :: Putter Word Source #

O(1). Write a single native machine word. The word is written 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. Values written this way are not portable to different endian or word sized machines, without conversion.

putWord16host :: Putter Word16 Source #

O(1). Write a Word16 in native host order and host endianness. For portability issues see putWordhost.

putWord32host :: Putter Word32 Source #

O(1). Write a Word32 in native host order and host endianness. For portability issues see putWordhost.

putWord64host :: Putter Word64 Source #

O(1). Write a Word64 in native host order On a 32 bit machine we write two host order Word32s, in big endian form. For portability issues see putWordhost.

Containers

putTwoOf :: Putter a -> Putter b -> Putter (a, b) Source #

putIArrayOf :: (Ix i, IArray a e) => Putter i -> Putter e -> Putter (a i e) Source #

putMapOf :: Putter k -> Putter a -> Putter (Map k a) Source #

putNested :: Putter Int -> Put -> Put Source #

Put a nested structure by first putting a length field and then putting the encoded value.