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

Portabilityportable to Hugs and GHC. Requires the FFI and some flexible instances
Stabilityunstable
MaintainerLennart Kolmodin <kolmodin@dtek.chalmers.se>

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 futher processed (for example, compressed with gzip).

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

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

Synopsis

The Binary class

class Binary t whereSource

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 parsing 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 -> PutSource

Encode a value in the Put monad.

get :: Get tSource

Decode a value in the Get monad

Instances

Binary Bool 
Binary Char 
Binary Double 
Binary Float 
Binary Int 
Binary Int8 
Binary Int16 
Binary Int32 
Binary Int64 
Binary Integer 
Binary Ordering 
Binary Word 
Binary Word8 
Binary Word16 
Binary Word32 
Binary Word64 
Binary () 
Binary ByteString 
Binary ByteString 
Binary IntSet 
Binary a => Binary [a] 
(Binary a, Integral a) => Binary (Ratio a) 
Binary a => Binary (Maybe a) 
Binary e => Binary (Tree e) 
Binary e => Binary (IntMap e) 
(Ord a, Binary a) => Binary (Set a) 
Binary e => Binary (Seq e) 
(Binary a, Binary b) => Binary (Either a b) 
(Binary a, Binary b) => Binary (a, b) 
(Binary i, Ix i, Binary e, IArray UArray e) => Binary (UArray i e) 
(Binary i, Ix i, Binary e) => Binary (Array i e) 
(Ord k, Binary k, Binary e) => Binary (Map k e) 
(Binary a, Binary b, Binary c) => Binary (a, b, c) 
(Binary a, Binary b, Binary c, Binary d) => Binary (a, b, c, d) 
(Binary a, Binary b, Binary c, Binary d, Binary e) => Binary (a, b, c, d, e) 
(Binary a, Binary b, Binary c, Binary d, Binary e, Binary f) => Binary (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) 
(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) 
(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) 
(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) 

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

The generation of Binary instances has been automated by a script using Scrap Your Boilerplate generics. Use the script here: http://darcs.haskell.org/binary/tools/derive/BinaryDerive.hs.

To derive the instance for a type, load this script into GHCi, and bring your type into scope. Your type can then have its Binary instances derived as follows:

 $ ghci -fglasgow-exts BinaryDerive.hs
 *BinaryDerive> :l Example.hs
 *Main> deriveM (undefined :: Drinks)

 instance Binary Main.Drinks where
      put (Beer a) = putWord8 0 >> put a
      put Coffee = putWord8 1
      put Tea = putWord8 2
      put EnergyDrink = putWord8 3
      put Water = putWord8 4
      put Wine = putWord8 5
      put Whisky = putWord8 6
      get = do
        tag_ <- getWord8
        case tag_ of
          0 -> get >>= \a -> return (Beer a)
          1 -> return Coffee
          2 -> return Tea
          3 -> return EnergyDrink
          4 -> return Water
          5 -> return Wine
          6 -> return Whisky

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

The Get and Put monads

data Get a Source

The Get monad is just a State monad carrying around the input ByteString We treat it as a strict state monad.

type Put = PutM ()Source

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

Useful helpers for writing instances

putWord8 :: Word8 -> PutSource

Efficiently write a byte into the output buffer

getWord8 :: Get Word8Source

Read a Word8 from the monad state

Binary serialisation

encode :: Binary a => a -> ByteStringSource

Encode a value using binary serialisation to a lazy ByteString.

decode :: Binary a => ByteString -> aSource

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

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 aSource

Lazily reconstruct a value previously written to a file.

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

 decodeFile f = return . decode =<< B.readFile f

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

 return . decode . decompress =<< B.readFile f

After contructing the data from the input file, decodeFile checks if the file is empty, and in doing so will force the associated file handle closed, if it is indeed empty. If the file is not empty, it is up to the decoding instance to consume the rest of the data, or otherwise finalise the resource.

module Data.Word