binary-0.8.5.1: Binary serialisation for Haskell values using lazy ByteStrings

CopyrightLennart Kolmodin
LicenseBSD3-style (see LICENSE)
MaintainerLennart Kolmodin <kolmodin@gmail.com>
Stabilitystable
PortabilityPortable to Hugs and GHC. Requires MPTCs
Safe HaskellSafe
LanguageHaskell98

Data.Binary.Put

Contents

Description

The Put monad. A monad for efficiently constructing lazy 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 #

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

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

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

Semigroup (PutM ()) Source # 

Methods

(<>) :: PutM () -> PutM () -> PutM () #

sconcat :: NonEmpty (PutM ()) -> PutM () #

stimes :: Integral b => b -> PutM () -> PutM () #

Monoid (PutM ()) Source # 

Methods

mempty :: PutM () #

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

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

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

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 :: Word8 -> Put Source #

Efficiently write a byte into the output buffer

putInt8 :: Int8 -> Put Source #

Efficiently write a signed byte into the output buffer

putByteString :: ByteString -> Put 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 :: ByteString -> Put Source #

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

Big-endian primitives

putWord16be :: Word16 -> Put Source #

Write a Word16 in big endian format

putWord32be :: Word32 -> Put Source #

Write a Word32 in big endian format

putWord64be :: Word64 -> Put Source #

Write a Word64 in big endian format

putInt16be :: Int16 -> Put Source #

Write an Int16 in big endian format

putInt32be :: Int32 -> Put Source #

Write an Int32 in big endian format

putInt64be :: Int64 -> Put Source #

Write an Int64 in big endian format

putFloatbe :: Float -> Put Source #

Write a Float in big endian IEEE-754 format.

putDoublebe :: Double -> Put Source #

Write a Double in big endian IEEE-754 format.

Little-endian primitives

putWord16le :: Word16 -> Put Source #

Write a Word16 in little endian format

putWord32le :: Word32 -> Put Source #

Write a Word32 in little endian format

putWord64le :: Word64 -> Put Source #

Write a Word64 in little endian format

putInt16le :: Int16 -> Put Source #

Write an Int16 in little endian format

putInt32le :: Int32 -> Put Source #

Write an Int32 in little endian format

putInt64le :: Int64 -> Put Source #

Write an Int64 in little endian format

putFloatle :: Float -> Put Source #

Write a Float in little endian IEEE-754 format.

putDoublele :: Double -> Put Source #

Write a Double in little endian IEEE-754 format.

Host-endian, unaligned writes

putWordhost :: Word -> Put 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 :: Word16 -> Put Source #

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

putWord32host :: Word32 -> Put Source #

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

putWord64host :: Word64 -> Put 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 :: Int -> Put 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 Int 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.

putInt16host :: Int16 -> Put Source #

O(1). Write an Int16 in native host order and host endianness. For portability issues see putInthost.

putInt32host :: Int32 -> Put Source #

O(1). Write an Int32 in native host order and host endianness. For portability issues see putInthost.

putInt64host :: Int64 -> Put Source #

O(1). Write an 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.

putFloathost :: Float -> Put Source #

Write a Float in native in IEEE-754 format and host endian.

putDoublehost :: Double -> Put Source #

Write a Double in native in IEEE-754 format and host endian.

Unicode

putCharUtf8 :: Char -> Put Source #

Write a character using UTF-8 encoding.

putStringUtf8 :: String -> Put Source #

Write a String using UTF-8 encoding.