data-msgpack-types-0.0.3: A Haskell implementation of MessagePack.

Safe HaskellSafe
LanguageHaskell2010

Data.MessagePack.Types.Object

Synopsis

Documentation

data Object Source #

Object Representation of MessagePack data.

Constructors

ObjectNil

represents nil

ObjectBool !Bool

represents true or false

ObjectInt !Int64

represents a negative integer

ObjectWord !Word64

represents a positive integer

ObjectFloat !Float

represents a floating point number

ObjectDouble !Double

represents a floating point number

ObjectStr !Text

extending Raw type represents a UTF-8 string

ObjectBin !ByteString

extending Raw type represents a byte array

ObjectArray ![Object]

represents a sequence of objects

ObjectMap ![(Object, Object)]

represents key-value pairs of objects

ObjectExt !Word8 !ByteString

represents a tuple of an integer and a byte array where the integer represents type information and the byte array represents data.

Instances
Eq Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

Methods

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

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

Ord Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

Read Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

Show Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

Generic Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

Associated Types

type Rep Object :: Type -> Type #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

Arbitrary Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

NFData Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

Methods

rnf :: Object -> () #

MessagePack Object Source # 
Instance details

Defined in Data.MessagePack.Types.Class

type Rep Object Source # 
Instance details

Defined in Data.MessagePack.Types.Object

type Rep Object = D1 (MetaData "Object" "Data.MessagePack.Types.Object" "data-msgpack-types-0.0.3-8hxRTu2qusGlTQiBkej7K" False) (((C1 (MetaCons "ObjectNil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ObjectBool" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))) :+: (C1 (MetaCons "ObjectInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64)) :+: (C1 (MetaCons "ObjectWord" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64)) :+: C1 (MetaCons "ObjectFloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Float))))) :+: ((C1 (MetaCons "ObjectDouble" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Double)) :+: (C1 (MetaCons "ObjectStr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: C1 (MetaCons "ObjectBin" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString)))) :+: (C1 (MetaCons "ObjectArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Object])) :+: (C1 (MetaCons "ObjectMap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(Object, Object)])) :+: C1 (MetaCons "ObjectExt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word8) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))))))