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

CopyrightLennart Kolmodin
LicenseBSD3-style (see LICENSE)
MaintainerLennart Kolmodin <[email protected]>
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 Source #

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

Encode a value in the Put monad.

get :: Get t Source #

Decode a value in the Get monad

putList :: [t] -> Put Source #

Encode a list of values in the Put monad. The default implementation may be overridden to be more efficient but must still have the same encoding format.

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

Encode a value in the Put monad.

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

Decode a value in the Get monad

Instances
Binary Bool Source # 
Instance details

Defined in Data.Binary.Class

Binary Char Source # 
Instance details

Defined in Data.Binary.Class

Binary Double Source # 
Instance details

Defined in Data.Binary.Class

Binary Float Source # 
Instance details

Defined in Data.Binary.Class

Binary Int Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Int -> Put Source #

get :: Get Int Source #

putList :: [Int] -> Put Source #

Binary Int8 Source # 
Instance details

Defined in Data.Binary.Class

Binary Int16 Source # 
Instance details

Defined in Data.Binary.Class

Binary Int32 Source # 
Instance details

Defined in Data.Binary.Class

Binary Int64 Source # 
Instance details

Defined in Data.Binary.Class

Binary Integer Source # 
Instance details

Defined in Data.Binary.Class

Binary Natural Source #

Since: 0.7.3.0

Instance details

Defined in Data.Binary.Class

Binary Ordering Source # 
Instance details

Defined in Data.Binary.Class

Binary Word Source # 
Instance details

Defined in Data.Binary.Class

Binary Word8 Source # 
Instance details

Defined in Data.Binary.Class

Binary Word16 Source # 
Instance details

Defined in Data.Binary.Class

Binary Word32 Source # 
Instance details

Defined in Data.Binary.Class

Binary Word64 Source # 
Instance details

Defined in Data.Binary.Class

Binary RuntimeRep Source #

@since 0.8.5.0. See

Instance details

Defined in Data.Binary.Class

Binary VecCount Source #

@since 0.8.5.0. See

Instance details

Defined in Data.Binary.Class

Binary VecElem Source #

@since 0.8.5.0. See

Instance details

Defined in Data.Binary.Class

Binary SomeTypeRep Source # 
Instance details

Defined in Data.Binary.Class

Binary () Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: () -> Put Source #

get :: Get () Source #

putList :: [()] -> Put Source #

Binary TyCon Source #

@since 0.8.5.0. See

Instance details

Defined in Data.Binary.Class

Binary KindRep Source #

@since 0.8.5.0. See

Instance details

Defined in Data.Binary.Class

Binary TypeLitSort Source #

@since 0.8.5.0. See

Instance details

Defined in Data.Binary.Class

Binary Void Source #

Since: 0.8.0.0

Instance details

Defined in Data.Binary.Class

Binary Version Source #

Since: 0.8.0.0

Instance details

Defined in Data.Binary.Class

Binary All Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: All -> Put Source #

get :: Get All Source #

putList :: [All] -> Put Source #

Binary Any Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Any -> Put Source #

get :: Get Any Source #

putList :: [Any] -> Put Source #

Binary Fingerprint Source #

Since: 0.7.6.0

Instance details

Defined in Data.Binary.Class

Binary ByteString Source # 
Instance details

Defined in Data.Binary.Class

Binary ShortByteString Source # 
Instance details

Defined in Data.Binary.Class

Binary ByteString Source # 
Instance details

Defined in Data.Binary.Class

Binary IntSet Source # 
Instance details

Defined in Data.Binary.Class

Binary a => Binary [a] Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: [a] -> Put Source #

get :: Get [a] Source #

putList :: [[a]] -> Put Source #

Binary a => Binary (Maybe a) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Maybe a -> Put Source #

get :: Get (Maybe a) Source #

putList :: [Maybe a] -> Put Source #

(Binary a, Integral a) => Binary (Ratio a) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Ratio a -> Put Source #

get :: Get (Ratio a) Source #

putList :: [Ratio a] -> Put Source #

Binary a => Binary (Complex a) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Complex a -> Put Source #

get :: Get (Complex a) Source #

putList :: [Complex a] -> Put Source #

Binary (Fixed a) Source #

Since: 0.8.0.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Fixed a -> Put Source #

get :: Get (Fixed a) Source #

putList :: [Fixed a] -> Put Source #

Binary a => Binary (Min a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Min a -> Put Source #

get :: Get (Min a) Source #

putList :: [Min a] -> Put Source #

Binary a => Binary (Max a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Max a -> Put Source #

get :: Get (Max a) Source #

putList :: [Max a] -> Put Source #

Binary a => Binary (First a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: First a -> Put Source #

get :: Get (First a) Source #

putList :: [First a] -> Put Source #

Binary a => Binary (Last a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Last a -> Put Source #

get :: Get (Last a) Source #

putList :: [Last a] -> Put Source #

Binary m => Binary (WrappedMonoid m) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Binary a => Binary (Option a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Option a -> Put Source #

get :: Get (Option a) Source #

putList :: [Option a] -> Put Source #

Binary a => Binary (First a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: First a -> Put Source #

get :: Get (First a) Source #

putList :: [First a] -> Put Source #

Binary a => Binary (Last a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Last a -> Put Source #

get :: Get (Last a) Source #

putList :: [Last a] -> Put Source #

Binary a => Binary (Dual a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Dual a -> Put Source #

get :: Get (Dual a) Source #

putList :: [Dual a] -> Put Source #

Binary a => Binary (Sum a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Sum a -> Put Source #

get :: Get (Sum a) Source #

putList :: [Sum a] -> Put Source #

Binary a => Binary (Product a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Product a -> Put Source #

get :: Get (Product a) Source #

putList :: [Product a] -> Put Source #

Binary a => Binary (NonEmpty a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Binary e => Binary (IntMap e) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: IntMap e -> Put Source #

get :: Get (IntMap e) Source #

putList :: [IntMap e] -> Put Source #

Binary e => Binary (Tree e) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Tree e -> Put Source #

get :: Get (Tree e) Source #

putList :: [Tree e] -> Put Source #

Binary e => Binary (Seq e) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Seq e -> Put Source #

get :: Get (Seq e) Source #

putList :: [Seq e] -> Put Source #

Binary a => Binary (Set a) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Set a -> Put Source #

get :: Get (Set a) Source #

putList :: [Set a] -> Put Source #

(Binary a, Binary b) => Binary (Either a b) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Either a b -> Put Source #

get :: Get (Either a b) Source #

putList :: [Either a b] -> Put Source #

Typeable a => Binary (TypeRep a) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: TypeRep a -> Put Source #

get :: Get (TypeRep a) Source #

putList :: [TypeRep a] -> Put Source #

(Binary a, Binary b) => Binary (a, b) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: (a, b) -> Put Source #

get :: Get (a, b) Source #

putList :: [(a, b)] -> Put Source #

(Binary i, Ix i, Binary e) => Binary (Array i e) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Array i e -> Put Source #

get :: Get (Array i e) Source #

putList :: [Array i e] -> Put Source #

(Binary a, Binary b) => Binary (Arg a b) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Arg a b -> Put Source #

get :: Get (Arg a b) Source #

putList :: [Arg a b] -> Put Source #

(Binary k, Binary e) => Binary (Map k e) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: Map k e -> Put Source #

get :: Get (Map k e) Source #

putList :: [Map k e] -> Put Source #

(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) Source # 
Instance details

Defined in Data.Binary.Class

Methods

put :: UArray i e -> Put Source #

get :: Get (UArray i e) Source #

putList :: [UArray i e] -> Put Source #

(Binary a, Binary b, Binary c) => Binary (a, b, c) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

get :: Get (a, b, c) Source #

putList :: [(a, b, c)] -> Put Source #

Binary (f a) => Binary (Alt f a) Source #

Since: 0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Alt f a -> Put Source #

get :: Get (Alt f a) Source #

putList :: [Alt f a] -> Put Source #

(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

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

putList :: [(a, b, c, d)] -> Put Source #

(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

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

putList :: [(a, b, c, d, e)] -> Put Source #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

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

putList :: [(a, b, c, d, e, f)] -> Put Source #

(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f, Binary g) => Binary (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

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

putList :: [(a, b, c, d, e, f, g)] -> Put Source #

(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) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

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

putList :: [(a, b, c, d, e, f, g, h)] -> Put Source #

(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) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

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

putList :: [(a, b, c, d, e, f, g, h, i)] -> Put Source #

(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) Source # 
Instance details

Defined in Data.Binary.Class

Methods

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

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

putList :: [(a, b, c, d, e, f, g, h, i, j)] -> Put Source #

Example

To serialise a custom type, an instance of Binary for that type is required. For example, suppose we have a data structure:

data Exp = IntE Int
         | OpE  String Exp Exp
   deriving Show

We can encode values of this type into bytestrings using the following instance, which proceeds by recursively breaking down the structure to serialise:

instance Binary Exp where
      put (IntE i)      = do put (0 :: Word8)
                             put i
      put (OpE s e1 e2) = do put (1 :: Word8)
                             put s
                             put e1
                             put e2

      get = do t <- get :: Get Word8
               case t of
                    0 -> do i <- get
                            return (IntE i)
                    1 -> do s  <- get
                            e1 <- get
                            e2 <- get
                            return (OpE s e1 e2)

Note how we write an initial tag byte to indicate each variant of the data type.

We can simplify the writing of get instances using monadic combinators:

      get = do tag <- getWord8
               case tag of
                   0 -> liftM  IntE get
                   1 -> liftM3 OpE  get get get

To serialise this to a bytestring, we use encode, which packs the data structure into a binary format, in a lazy bytestring

> let e = OpE "*" (IntE 7) (OpE "/" (IntE 4) (IntE 2))
> let v = encode e

Where v is a binary encoded data structure. To reconstruct the original data, we use decode

> decode v :: Exp
OpE "*" (IntE 7) (OpE "/" (IntE 4) (IntE 2))

The lazy ByteString that results from encode can be written to disk, and read from disk using Data.ByteString.Lazy IO functions, such as hPutStr or writeFile:

> writeFile "/tmp/exp.txt" (encode e)

And read back with:

> readFile "/tmp/exp.txt" >>= return . decode :: IO Exp
OpE "*" (IntE 7) (OpE "/" (IntE 4) (IntE 2))

We can also directly serialise a value to and from a Handle, or a file:

> v <- decodeFile  "/tmp/exp.txt" :: IO Exp
OpE "*" (IntE 7) (OpE "/" (IntE 4) (IntE 2))

And write a value to disk

> encodeFile "/tmp/a.txt" v

Generic support

Beginning with GHC 7.2, it is possible to use binary serialization without writing any instance boilerplate code.

{-# LANGUAGE DeriveGeneric #-}

import Data.Binary
import GHC.Generics (Generic)

data Foo = Foo
         deriving (Generic)

-- GHC will automatically fill out the instance
instance Binary Foo

This mechanism makes use of GHC's efficient built-in generics support.

class GBinaryGet f where Source #

Minimal complete definition

gget

Methods

gget :: Get (f t) Source #

Instances
GBinaryGet (V1 :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gget :: Get (V1 t) Source #

GBinaryGet (U1 :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gget :: Get (U1 t) Source #

Binary a => GBinaryGet (K1 i a :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gget :: Get (K1 i a t) Source #

(GSumGet a, GSumGet b, SumSize a, SumSize b) => GBinaryGet (a :+: b :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gget :: Get ((a :+: b) t) Source #

(GBinaryGet a, GBinaryGet b) => GBinaryGet (a :*: b :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gget :: Get ((a :*: b) t) Source #

GBinaryGet a => GBinaryGet (M1 i c a :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gget :: Get (M1 i c a t) Source #

class GBinaryPut f where Source #

Minimal complete definition

gput

Methods

gput :: f t -> Put Source #

Instances
GBinaryPut (V1 :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gput :: V1 t -> Put Source #

GBinaryPut (U1 :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gput :: U1 t -> Put Source #

Binary a => GBinaryPut (K1 i a :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gput :: K1 i a t -> Put Source #

(GSumPut a, GSumPut b, SumSize a, SumSize b) => GBinaryPut (a :+: b :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gput :: (a :+: b) t -> Put Source #

(GBinaryPut a, GBinaryPut b) => GBinaryPut (a :*: b :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gput :: (a :*: b) t -> Put Source #

GBinaryPut a => GBinaryPut (M1 i c a :: * -> *) Source # 
Instance details

Defined in Data.Binary.Generic

Methods

gput :: M1 i c a t -> Put Source #

The Get and Put monads

data Get a Source #

Instances
Monad Get Source # 
Instance details

Defined in Data.Binary.Get.Internal

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 Source # 
Instance details

Defined in Data.Binary.Get.Internal

Methods

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

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

MonadFail Get Source # 
Instance details

Defined in Data.Binary.Get.Internal

Methods

fail :: String -> Get a Source #

Applicative Get Source # 
Instance details

Defined in Data.Binary.Get.Internal

Methods

pure :: a -> Get a Source #

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

liftA2 :: (a -> b -> c) -> Get a -> Get b -> Get c Source #

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

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

Alternative Get Source #

Since: 0.7.0.0

Instance details

Defined in Data.Binary.Get.Internal

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

Since: 0.7.1.0

Instance details

Defined in Data.Binary.Get.Internal

Methods

mzero :: Get a Source #

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

type Put = PutM () Source #

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

Useful helpers for writing instances

putWord8 :: Word8 -> Put Source #

Efficiently write a byte into the output buffer

getWord8 :: Get Word8 Source #

Read a Word8 from the monad state

Binary serialisation

encode :: Binary a => a -> ByteString Source #

Encode a value using binary serialisation to a lazy ByteString.

decode :: Binary a => ByteString -> a Source #

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

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

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 () Source #

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

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

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