beamable-0.1.1.1: Generic serializer/deserializer with compact representation

Safe HaskellNone

Data.Beamable

Description

To serialize your own datatype first you need to add DeriveGeneric pragma to the module where your data is declared, derive Generic instance for that datatype and add empty instance declaration for Beamable class

 {-# LANGUAGE DeriveGeneric #-}
 data Foo = Foo1 Int | Foo2 String deriving (Generic}
 instance Beamable Foo

Synopsis

Documentation

class Beamable a whereSource

Methods

beam :: a -> BuilderSource

Serialize value into Builder

unbeam :: ByteString -> (a, ByteString)Source

Deserialize next value from ByteString, also returns leftovers

typeSign :: Beamable a => a -> Word64Source

Get type signature of arbitrary Beamable datatatype encoded as Word64 hash with all constructors and datatypes in it. It's preferable to use typeSign against typeSignR, because implementation of later might change.

encode :: Beamable a => a -> ByteStringSource

Encode single value into compact bytestring, for encoding large number of values use beam and toByteString from Blaze.ByteString.Builder

decode :: Beamable a => ByteString -> aSource

Decode single value from bytestring. ByteString must be exactly correct size

encodeSigned :: Beamable a => a -> ByteStringSource

Encode single value with extra type singature added, this adds 8 bytes to binary representation, but will prevent decoding using invalid data instances

decodeSigned :: Beamable a => ByteString -> aSource

Decode single value encoded with encodeSigned

data Phantom a Source

Phantom a has just one possible value, like (), and is encoded as a 0-byte sequence. However, its typeSign depends on the typeSign of its parameter.

Constructors

Phantom 

Instances

data Builder

Instances

toByteString :: Builder -> ByteString

Run the builder to construct a strict bytestring containing the sequence of bytes denoted by the builder. This is done by first serializing to a lazy bytestring and then packing its chunks to a appropriately sized strict bytestring.

 toByteString = packChunks . toLazyByteString

Note that toByteString is a Monoid homomorphism.

 toByteString mempty          == mempty
 toByteString (x `mappend` y) == toByteString x `mappend` toByteString y

However, in the second equation, the left-hand-side is generally faster to execute.