Copyright | Lennart Kolmodin |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Lennart Kolmodin <kolmodin@gmail.com> |
Stability | unstable |
Portability | portable to Hugs and GHC. Requires the FFI and some flexible instances. |
Safe Haskell | Trustworthy |
Language | Haskell98 |
Binary serialisation of Haskell values to and from lazy ByteString
s.
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 GBinary
.
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.
- class Binary t where
- class GBinary f where
- data Get a
- type Put = PutM ()
- putWord8 :: Word8 -> Put
- getWord8 :: Get Word8
- encode :: Binary a => a -> ByteString
- decode :: Binary a => ByteString -> a
- decodeOrFail :: Binary a => ByteString -> Either (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
- encodeFile :: Binary a => FilePath -> a -> IO ()
- decodeFile :: Binary a => FilePath -> IO a
- decodeFileOrFail :: Binary a => FilePath -> IO (Either (ByteOffset, String) a)
- module Data.Word
The Binary class
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.
Nothing
Encode a value in the Put monad.
Decode a value in the Get monad
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.
The Get and Put monads
Useful helpers for writing instances
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
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.
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