| Copyright | Lennart Kolmodin Galois Inc. 2009 | 
|---|---|
| License | BSD3-style (see LICENSE) | 
| Maintainer | Trevor Elliott <trevor@galois.com> | 
| Stability | Portability : | 
| Safe Haskell | Safe | 
| Language | Haskell2010 | 
Data.Serialize.Put
Contents
Description
The Put monad. A monad for efficiently constructing bytestrings.
Synopsis
- type Put = PutM ()
- newtype PutM a = Put {- unPut :: PairS a
 
- type Putter a = a -> Put
- runPut :: Put -> ByteString
- runPutM :: PutM a -> (a, ByteString)
- runPutLazy :: Put -> ByteString
- runPutMLazy :: PutM a -> (a, ByteString)
- runPutMBuilder :: PutM a -> (a, Builder)
- putBuilder :: Putter Builder
- execPut :: PutM a -> Builder
- flush :: Put
- putWord8 :: Putter Word8
- putInt8 :: Putter Int8
- putByteString :: Putter ByteString
- putLazyByteString :: Putter ByteString
- putShortByteString :: Putter ShortByteString
- putWord16be :: Putter Word16
- putWord32be :: Putter Word32
- putWord64be :: Putter Word64
- putInt16be :: Putter Int16
- putInt32be :: Putter Int32
- putInt64be :: Putter Int64
- putWord16le :: Putter Word16
- putWord32le :: Putter Word32
- putWord64le :: Putter Word64
- putInt16le :: Putter Int16
- putInt32le :: Putter Int32
- putInt64le :: Putter Int64
- putWordhost :: Putter Word
- putWord16host :: Putter Word16
- putWord32host :: Putter Word32
- putWord64host :: Putter Word64
- putInthost :: Putter Int
- putInt16host :: Putter Int16
- putInt32host :: Putter Int32
- putInt64host :: Putter Int64
- putTwoOf :: Putter a -> Putter b -> Putter (a, b)
- putListOf :: Putter a -> Putter [a]
- putIArrayOf :: (Ix i, IArray a e) => Putter i -> Putter e -> Putter (a i e)
- putSeqOf :: Putter a -> Putter (Seq a)
- putTreeOf :: Putter a -> Putter (Tree a)
- putMapOf :: Putter k -> Putter a -> Putter (Map k a)
- putIntMapOf :: Putter Int -> Putter a -> Putter (IntMap a)
- putSetOf :: Putter a -> Putter (Set a)
- putIntSetOf :: Putter Int -> Putter IntSet
- putMaybeOf :: Putter a -> Putter (Maybe a)
- putEitherOf :: Putter a -> Putter b -> Putter (Either a b)
- putNested :: Putter Int -> Put -> Put
The Put type
The PutM type. A Writer monad over the efficient Builder monoid.
runPutLazy :: Put -> ByteString Source #
Run the Put monad with a serialiser
runPutMLazy :: PutM a -> (a, ByteString) Source #
Run the Put monad with a serialiser
runPutMBuilder :: PutM a -> (a, Builder) Source #
Flushing the implicit parse state
Pop the ByteString we have constructed so far, if any, yielding a new chunk in the result ByteString.
Primitives
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
putInt16be :: Putter Int16 Source #
Write a Int16 in big endian format
putInt32be :: Putter Int32 Source #
Write a Int32 in big endian format
putInt64be :: Putter Int64 Source #
Write a Int64 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
putInt16le :: Putter Int16 Source #
Write a Int16 in little endian format
putInt32le :: Putter Int32 Source #
Write a Int32 in little endian format
putInt64le :: Putter Int64 Source #
Write a Int64 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.
putInthost :: Putter Int Source #
O(1). Write a single native machine int. The int is written in host order, host endian form, for the machine you're on. On a 64 bit machine the Int is an 8 byte value, on a 32 bit machine, 4 bytes. Values written this way are not portable to different endian or int sized machines, without conversion.
putInt16host :: Putter Int16 Source #
O(1). Write a Int16 in native host order and host endianness.
 For portability issues see putInthost.
putInt32host :: Putter Int32 Source #
O(1). Write a Int32 in native host order and host endianness.
 For portability issues see putInthost.
putInt64host :: Putter Int64 Source #
O(1). Write a Int64 in native host order
 On a 32 bit machine we write two host order Int32s, in big endian form.
 For portability issues see putInthost.