packer-messagepack-0.1.0.0: MessagePack Serialization an Deserialization for Packer

Safe HaskellNone
LanguageHaskell2010

Data.Packer.MessagePack

Synopsis

Documentation

class ToMsgPack a where Source #

Type class for values which support MessagePack serialization.

Minimal complete definition

toMsgPack, msgPackSize

Methods

toMsgPack :: a -> Packing () Source #

Serializes the provided value as MessagePack within a Packing monad.

msgPackSize :: MonadThrow m => a -> m Int Source #

Computes the size of the serialized data in bytes.

Instances

ToMsgPack Bool Source #

ToMsgPack instance for boolean values. This implements serialization for the MessagePack bool format family.

ToMsgPack Double Source #

ToMsgPack instance for double values. This implements serialization for the MessagePack float64 format family.

ToMsgPack Float Source #

ToMsgPack instance for float values. This implements serialization for the MessagePack float32 format family.

ToMsgPack Int Source #

ToMsgPack instance for Int values. This implements serialization for those signed values within the MessagePack int format family, which fit in an Int (at least positive fixint, negative fixint, int8, int16).

ToMsgPack Int8 Source #

ToMsgPack instance for Int8 values. This implements serialization for those signed values within the MessagePack int format family, which fit in an Int8: positive fixint, negative fixint, int8.

ToMsgPack Int16 Source #

ToMsgPack instance for Int16 values. This implements serialization for those signed values within the MessagePack int format family, which fit in an Int16: positive fixint, negative fixint, int8, int16.

ToMsgPack Int32 Source #

ToMsgPack instance for Int32 values. This implements serialization for those signed values within the MessagePack int format family, which fit in an Int32: positive fixint, negative fixint, int8, int16, int32.

ToMsgPack Int64 Source #

ToMsgPack instance for Int64 values. This implements serialization for those signed values within the MessagePack int format family, which fit in an Int64: positive fixint, negative fixint, int8, int16, int32, int64.

ToMsgPack Word8 Source #

ToMsgPack instance for Word8 values. This implements serialization for those unsigned values within the MessagePack int format family, which fit in a Word8: positive fixint, uint8.

ToMsgPack Word16 Source #

ToMsgPack instance for Word16 values. This implements serialization for those unsigned values within the MessagePack int format family, which fit in a Word16: positive fixint, uint8, uint16.

ToMsgPack Word32 Source #

ToMsgPack instance for Word32 values. This implements serialization for those unsigned values within the MessagePack int format family, which fit in a Word32: positive fixint, uint8, uint16, uint32.

ToMsgPack Word64 Source #

ToMsgPack instance for '64' values. This implements serialization for those unsigned values within the MessagePack int format family, which fit in a Word64: positive fixint, uint8, uint16, uint32, uint64.

ToMsgPack ByteString Source #

ToMsgPack instance for ByteStrings. This implements serialization for the MessagePack bin format family for raw binary strings up to a length of 2^32 - 1.

ToMsgPack Text Source #

ToMsgPack instance for Texts. This implements serialization for the MessagePack str format family for UTF8 encoded strings up to a length of 2^32 - 1.

ToMsgPack Object Source #

ToMsgPack instance for general MessagePack Objects.

ToMsgPack a => ToMsgPack [a] Source #

ToMsgPack instance for lists. This implements serialization for the MessagePack array format family for collections of up to a length of 2^32 - 1.

Methods

toMsgPack :: [a] -> Packing () Source #

msgPackSize :: MonadThrow m => [a] -> m Int Source #

(ToMsgPack a, ToMsgPack b) => ToMsgPack (a, b) Source #

ToMsgPack instance for pairs. This instance serializes the first value of the pair and then the second value of the pair.

Methods

toMsgPack :: (a, b) -> Packing () Source #

msgPackSize :: MonadThrow m => (a, b) -> m Int Source #

(ToMsgPack k, ToMsgPack v) => ToMsgPack (Map k v) Source #

FromMsgPack instance for maps. This implements deserialization for the MessagePack map format family for maps of up to 2^32 - 1 keys resp. values.

Methods

toMsgPack :: Map k v -> Packing () Source #

msgPackSize :: MonadThrow m => Map k v -> m Int Source #

class FromMsgPack a where Source #

Type class for values which support MessagePack deserialization.

Minimal complete definition

fromMsgPack

Methods

fromMsgPack :: Unpacking a Source #

Deserializes a MessagePack value in an Unpacking monad.

Instances

FromMsgPack Bool Source #

FromMsgPack instance for boolean values. This implements deserialization for the MessagePack bool format family.

FromMsgPack Double Source #

FromMsgPack instance for double values. This implements deserialization for the MessagePack float64 format family.

FromMsgPack Float Source #

FromMsgPack instance for float values. This implements deserialization for the MessagePack float32 format family.

FromMsgPack Int Source #

FromMsgPack instance for Int values. This implements deserialization for those signed values within the MessagePack int format family, which fit in an Int (at least positive fixint, negative fixint, int8, int16). Deserializing bigger values will cause a MsgPackDeserializationFailure exception to be thrown.

FromMsgPack Int8 Source #

FromMsgPack instance for Int8 values. This implements deserialization for those signed values within the MessagePack int format family, which fit in an Int8: positive fixint, negative fixint, int8. Deserializing bigger values will cause a MsgPackDeserializationFailure exception to be thrown.

FromMsgPack Int16 Source #

FromMsgPack instance for Int16 values. This implements deserialization for those unsigned values within the MessagePack int format family, which fit in an Int16: positive fixint, negative fixint, int8, int16. Deserializing bigger values will cause a MsgPackDeserializationFailure exception to be thrown.

FromMsgPack Int32 Source #

FromMsgPack instance for Int32 values. This implements deserialization for those unsigned values within the MessagePack int format family, which fit in an Int16: positive fixint, negative fixint, int8, int16, int32. Deserializing bigger values will cause a MsgPackDeserializationFailure exception to be thrown.

FromMsgPack Int64 Source #

FromMsgPack instance for Int64 values. This implements deserialization for those unsigned values within the MessagePack int format family, which fit in an Int64: positive fixint, negative fixint, int8, int16, int32, int64.

FromMsgPack Word8 Source #

FromMsgPack instance for Word8 values. This implements deserialization for those unsigned values within the MessagePack int format family, which fit in a Word8: positive fixint, uint8. Deserializing bigger values will cause a MsgPackDeserializationFailure exception to be thrown.

FromMsgPack Word16 Source #

FromMsgPack instance for Word16 values. This implements deserialization for those unsigned values within the MessagePack int format family, which fit in a Word16: positive fixint, uint8, uint16. Deserializing bigger values will cause a MsgPackDeserializationFailure exception to be thrown.

FromMsgPack Word32 Source #

FromMsgPack instance for Word32 values. This implements deserialization for those unsigned values within the MessagePack int format family, which fit in a Word32: positive fixint, uint8, uint16, uint32. Deserializing bigger values will cause a MsgPackDeserializationFailure exception to be thrown.

FromMsgPack Word64 Source #

FromMsgPack instance for Word64 values. This implements deserialization for those unsigned values within the MessagePack int format family, which fit in a Word64: positive fixint, uint8, uint16, uint32, uint64.

FromMsgPack ByteString Source #

FromMsgPack instance for ByteStrings. This implements deserialization for the MessagePack bin format family for raw binary strings up to a length of 2^32 - 1.

FromMsgPack Text Source #

FromMsgPack instance for Text. This implements deserialization for the MessagePack str format family for UTF8 encoded strings up to a length of 2^32 - 1.

FromMsgPack Object Source #

FromMsgPack instance for general MessagePack Objects.

FromMsgPack a => FromMsgPack [a] Source #

FromMsgPack instance for lists. This implements deserialization for the MessagePack array format family for collections of up to a length of 2^32 - 1.

(FromMsgPack a, FromMsgPack b) => FromMsgPack (a, b) Source #

FromMsgPack instance for pairs. This instance deserializes the first value of the pair and then the second value of the pair.

Methods

fromMsgPack :: Unpacking (a, b) Source #

(Ord k, Ord v, FromMsgPack k, FromMsgPack v) => FromMsgPack (Map k v) Source #

FromMsgPack instance for Maps. This implements deserialization for the MessagePack map format family for maps of up to 2^32 - 1 keys resp. values.

Methods

fromMsgPack :: Unpacking (Map k v) Source #

data Object Source #

Data type wrapping any supported MessagePack value.

Instances

Eq Object Source # 

Methods

(==) :: Object -> Object -> Bool #

(/=) :: Object -> Object -> Bool #

Ord Object Source # 
Show Object Source # 
Generic Object Source # 

Associated Types

type Rep Object :: * -> * #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

FromMsgPack Object Source #

FromMsgPack instance for general MessagePack Objects.

ToMsgPack Object Source #

ToMsgPack instance for general MessagePack Objects.

type Rep Object Source # 
type Rep Object = D1 (MetaData "Object" "Data.Packer.MessagePack.Internal.Types" "packer-messagepack-0.1.0.0-9sxXYChYyCWBvOrKsdVUrj" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "ObjectString" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "ObjectBinary" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))) ((:+:) (C1 (MetaCons "ObjectUInt" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))) ((:+:) (C1 (MetaCons "ObjectInt" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64))) (C1 (MetaCons "ObjectBool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))) ((:+:) ((:+:) (C1 (MetaCons "ObjectFloat32" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))) (C1 (MetaCons "ObjectFloat64" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))) ((:+:) (C1 (MetaCons "ObjectArray" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Object]))) ((:+:) (C1 (MetaCons "ObjectMap" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Object Object)))) (C1 (MetaCons "ObjectNil" PrefixI False) U1)))))