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

CopyrightLennart Kolmodin
LicenseBSD3-style (see LICENSE)
MaintainerLennart Kolmodin <kolmodin@gmail.com>
Stabilityunstable
Portabilityportable to Hugs and GHC. Requires the FFI and some flexible instances.
Safe HaskellTrustworthy
LanguageHaskell98

Data.Binary

Contents

Description

Binary serialisation of Haskell values to and from lazy ByteStrings. The Binary library provides methods for encoding Haskell values as streams of bytes directly in memory. The resulting ByteString can then be written to disk, sent over the network, or further processed (for example, compressed with gzip).

The binary package is notable in that it provides both pure, and high performance serialisation.

Values encoded using the Binary class are always encoded in network order (big endian) form, and encoded data should be portable across machine endianness, word size, or compiler version. For example, data encoded using the Binary class could be written on any machine, and read back on any another.

If the specifics of the data format is not important to you, for example, you are more interested in serializing and deserializing values than in which format will be used, it is possible to derive Binary instances using the generic support. See GBinaryGet and GBinaryPut.

If you have specific requirements about the encoding format, you can use the encoding and decoding primitives directly, see the modules Data.Binary.Get and Data.Binary.Put.

Synopsis

The Binary class

class Binary t where

The Binary class provides put and get, methods to encode and decode a Haskell value to a lazy ByteString. It mirrors the Read and Show classes for textual representation of Haskell types, and is suitable for serialising Haskell values to disk, over the network.

For decoding and generating simple external binary formats (e.g. C structures), Binary may be used, but in general is not suitable for complex protocols. Instead use the Put and Get primitives directly.

Instances of Binary should satisfy the following property:

decode . encode == id

That is, the get and put methods should be the inverse of each other. A range of instances are provided for basic Haskell types.

Methods

put :: t -> Put

Encode a value in the Put monad.

get :: Get t

Decode a value in the Get monad

put :: (Generic t, GBinaryPut (Rep t)) => t -> Put

Encode a value in the Put monad.

get :: (Generic t, GBinaryGet (Rep t)) => Get t

Decode a value in the Get monad

Instances

Binary Bool 

Methods

put :: Bool -> Put

get :: Get Bool

Binary Char 

Methods

put :: Char -> Put

get :: Get Char

Binary Double 

Methods

put :: Double -> Put

get :: Get Double

Binary Float 

Methods

put :: Float -> Put

get :: Get Float

Binary Int 

Methods

put :: Int -> Put

get :: Get Int

Binary Int8 

Methods

put :: Int8 -> Put

get :: Get Int8

Binary Int16 

Methods

put :: Int16 -> Put

get :: Get Int16

Binary Int32 

Methods

put :: Int32 -> Put

get :: Get Int32

Binary Int64 

Methods

put :: Int64 -> Put

get :: Get Int64

Binary Integer 

Methods

put :: Integer -> Put

get :: Get Integer

Binary Ordering 

Methods

put :: Ordering -> Put

get :: Get Ordering

Binary Word 

Methods

put :: Word -> Put

get :: Get Word

Binary Word8 

Methods

put :: Word8 -> Put

get :: Get Word8

Binary Word16 

Methods

put :: Word16 -> Put

get :: Get Word16

Binary Word32 

Methods

put :: Word32 -> Put

get :: Get Word32

Binary Word64 

Methods

put :: Word64 -> Put

get :: Get Word64

Binary () 

Methods

put :: () -> Put

get :: Get ()

Binary Void

Since: 0.8.0.0

Methods

put :: Void -> Put

get :: Get Void

Binary Natural

Since: 0.7.3.0

Methods

put :: Natural -> Put

get :: Get Natural

Binary Version

Since: 0.8.0.0

Methods

put :: Version -> Put

get :: Get Version

Binary Fingerprint

Since: 0.7.6.0

Binary ByteString 
Binary ShortByteString 
Binary ByteString 
Binary IntSet 

Methods

put :: IntSet -> Put

get :: Get IntSet

Binary a => Binary [a] 

Methods

put :: [a] -> Put

get :: Get [a]

Binary a => Binary (Maybe a) 

Methods

put :: Maybe a -> Put

get :: Get (Maybe a)

(Binary a, Integral a) => Binary (Ratio a) 

Methods

put :: Ratio a -> Put

get :: Get (Ratio a)

Binary (Fixed a)

Since: 0.8.0.0

Methods

put :: Fixed a -> Put

get :: Get (Fixed a)

Binary e => Binary (IntMap e) 

Methods

put :: IntMap e -> Put

get :: Get (IntMap e)

Binary a => Binary (Set a) 

Methods

put :: Set a -> Put

get :: Get (Set a)

Binary e => Binary (Tree e) 

Methods

put :: Tree e -> Put

get :: Get (Tree e)

Binary e => Binary (Seq e) 

Methods

put :: Seq e -> Put

get :: Get (Seq e)

(Binary a, Binary b) => Binary (Either a b) 

Methods

put :: Either a b -> Put

get :: Get (Either a b)

(Binary a, Binary b) => Binary (a, b) 

Methods

put :: (a, b) -> Put

get :: Get (a, b)

(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) 

Methods

put :: UArray i e -> Put

get :: Get (UArray i e)

(Binary i, Ix i, Binary e) => Binary (Array i e) 

Methods

put :: Array i e -> Put

get :: Get (Array i e)

(Binary k, Binary e) => Binary (Map k e) 

Methods

put :: Map k e -> Put

get :: Get (Map k e)

(Binary a, Binary b, Binary c) => Binary (a, b, c) 

Methods

put :: (a, b, c) -> Put

get :: Get (a, b, c)

(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) 

Methods

put :: (a, b, c, d) -> Put

get :: Get (a, b, c, d)

(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) 

Methods

put :: (a, b, c, d, e) -> Put

get :: Get (a, b, c, d, e)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) 

Methods

put :: (a, b, c, d, e, f) -> Put

get :: Get (a, b, c, d, e, f)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) 

Methods

put :: (a, b, c, d, e, f, g) -> Put

get :: Get (a, b, c, d, e, f, g)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h) => Binary (a, b, c, d, e, f, g, h) 

Methods

put :: (a, b, c, d, e, f, g, h) -> Put

get :: Get (a, b, c, d, e, f, g, h)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i) => Binary (a, b, c, d, e, f, g, h, i) 

Methods

put :: (a, b, c, d, e, f, g, h, i) -> Put

get :: Get (a, b, c, d, e, f, g, h, i)

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g, Binary h, Binary i, Binary j) => Binary (a, b, c, d, e, f, g, h, i, j) 

Methods

put :: (a, b, c, d, e, f, g, h, i, j) -> Put

get :: Get (a, b, c, d, e, f, g, h, i, j)

Example

 

Generic support

 

class GBinaryGet f where

Minimal complete definition

gget

Methods

gget :: Get (f t)

class GBinaryPut f where

Minimal complete definition

gput

Methods

gput :: f t -> Put

The Get and Put monads

data Get a

Instances

Monad Get 

Methods

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

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

return :: a -> Get a Source

fail :: String -> Get a Source

Functor Get 

Methods

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

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

MonadFail Get 

Methods

fail :: String -> Get a Source

Applicative Get 

Methods

pure :: a -> Get a Source

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

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

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

Alternative Get

Since: 0.7.0.0

Methods

empty :: Get a Source

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

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

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

MonadPlus Get

Since: 0.7.1.0

Methods

mzero :: Get a Source

mplus :: Get a -> Get a -> Get a Source

type Put = PutM ()

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

Useful helpers for writing instances

putWord8 :: Word8 -> Put

Efficiently write a byte into the output buffer

getWord8 :: Get Word8

Read a Word8 from the monad state

Binary serialisation

encode :: Binary a => a -> ByteString

Encode a value using binary serialisation to a lazy ByteString.

decode :: Binary a => ByteString -> a

Decode a value from a lazy ByteString, reconstructing the original structure.

decodeOrFail :: Binary a => ByteString -> Either (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)

Decode a value from a lazy ByteString. Returning Left on failure and Right on success. In both cases the unconsumed input and the number of consumed bytes is returned. In case of failure, a human-readable error message will be returned as well.

Since: 0.7.0.0

IO functions for serialisation

encodeFile :: Binary a => FilePath -> a -> IO ()

Lazily serialise a value to a file.

This is just a convenience function, it's defined simply as:

encodeFile f = B.writeFile f . encode

So for example if you wanted to compress as well, you could use:

B.writeFile f . compress . encode

decodeFile :: Binary a => FilePath -> IO a

Decode a value from a file. In case of errors, error will be called with the error message.

Since: 0.7.0.0

decodeFileOrFail :: Binary a => FilePath -> IO (Either (ByteOffset, String) a)

Decode a value from a file. In case of success, the value will be returned in Right. In case of decoder errors, the error message together with the byte offset will be returned.

module Data.Word