Safe Haskell | None |
---|
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
- class Beamable a where
- beam :: a -> Builder
- unbeam :: ByteString -> (a, ByteString)
- typeSign :: Beamable a => a -> Word64
- encode :: Beamable a => a -> ByteString
- decode :: Beamable a => ByteString -> a
- encodeSigned :: Beamable a => a -> ByteString
- decodeSigned :: Beamable a => ByteString -> a
- data Decoder a
- encodeLive :: Beamable a => a -> ByteString
- decodeLive :: Beamable a => Decoder a
- feed :: Beamable a => Decoder a -> ByteString -> Either (Decoder a) (a, ByteString)
- data Phantom a = Phantom
- data Builder
- toByteString :: Builder -> ByteString
Documentation
Methods
Serialize value into Builder
unbeam :: ByteString -> (a, ByteString)Source
Deserialize next value from ByteString
, also returns leftovers
Instances
Beamable Bool | |
Beamable Char | |
Beamable Double | |
Beamable Float | |
Beamable Int | |
Beamable Int8 | |
Beamable Int16 | |
Beamable Int32 | |
Beamable Int64 | |
Beamable Integer | |
Beamable Word | |
Beamable Word8 | |
Beamable Word16 | |
Beamable Word32 | |
Beamable Word64 | |
Beamable () | |
Beamable ByteString | |
Beamable ByteString | |
Beamable TypeSign | |
Beamable a => Beamable [a] | |
Beamable a => Beamable (Maybe a) | |
Beamable a => Beamable (Phantom a) | |
(Beamable a, Beamable b) => Beamable (Either a b) | |
(Beamable a, Beamable b) => Beamable (a, b) | |
(Beamable a, Beamable b, Beamable c) => Beamable (a, b, c) | |
(Beamable a, Beamable b, Beamable c, Beamable d) => Beamable (a, b, c, d) | |
(Beamable a, Beamable b, Beamable c, Beamable d, Beamable e) => Beamable (a, b, c, d, e) | |
(Beamable a, Beamable b, Beamable c, Beamable d, Beamable e, Beamable f) => Beamable (a, b, c, d, e, f) | |
(Beamable a, Beamable b, Beamable c, Beamable d, Beamable e, Beamable f, Beamable g) => Beamable (a, b, c, d, e, f, g) |
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
encodeLive :: Beamable a => a -> ByteStringSource
decodeLive :: Beamable a => Decoder aSource
feed :: Beamable a => Decoder a -> ByteString -> Either (Decoder a) (a, ByteString)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 |
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
is a toByteString
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.