{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE StrictData         #-}
{-# LANGUAGE Trustworthy        #-}
module Data.MessagePack.Types.Object
    ( Object (..)
    ) where

import           Control.DeepSeq (NFData (..))
import qualified Data.ByteString as S
import           Data.Int        (Int64)
import qualified Data.Text       as T
import           Data.Typeable   (Typeable)
import qualified Data.Vector     as V
import           Data.Word       (Word64, Word8)
import           GHC.Generics    (Generic)


-- | Object Representation of MessagePack data.
data Object
    = ObjectNil
      -- ^ represents nil
    | ObjectBool                  Bool
      -- ^ represents true or false
    | ObjectInt    {-# UNPACK #-} Int64
      -- ^ represents a negative integer
    | ObjectWord   {-# UNPACK #-} Word64
      -- ^ represents a positive integer
    | ObjectFloat  {-# UNPACK #-} Float
      -- ^ represents a floating point number
    | ObjectDouble {-# UNPACK #-} Double
      -- ^ represents a floating point number
    | ObjectStr                   T.Text
      -- ^ extending Raw type represents a UTF-8 string
    | ObjectBin                   S.ByteString
      -- ^ extending Raw type represents a byte array
    | ObjectArray                 (V.Vector Object)
      -- ^ represents a sequence of objects
    | ObjectMap                   (V.Vector (Object, Object))
      -- ^ represents key-value pairs of objects
    | ObjectExt    {-# UNPACK #-} Word8 S.ByteString
      -- ^ represents a tuple of an integer and a byte array where
      -- the integer represents type information and the byte array represents data.
    deriving (ReadPrec [Object]
ReadPrec Object
Int -> ReadS Object
ReadS [Object]
(Int -> ReadS Object)
-> ReadS [Object]
-> ReadPrec Object
-> ReadPrec [Object]
-> Read Object
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Object]
$creadListPrec :: ReadPrec [Object]
readPrec :: ReadPrec Object
$creadPrec :: ReadPrec Object
readList :: ReadS [Object]
$creadList :: ReadS [Object]
readsPrec :: Int -> ReadS Object
$creadsPrec :: Int -> ReadS Object
Read, Int -> Object -> ShowS
[Object] -> ShowS
Object -> String
(Int -> Object -> ShowS)
-> (Object -> String) -> ([Object] -> ShowS) -> Show Object
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Object] -> ShowS
$cshowList :: [Object] -> ShowS
show :: Object -> String
$cshow :: Object -> String
showsPrec :: Int -> Object -> ShowS
$cshowsPrec :: Int -> Object -> ShowS
Show, Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq, Eq Object
Eq Object
-> (Object -> Object -> Ordering)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Bool)
-> (Object -> Object -> Object)
-> (Object -> Object -> Object)
-> Ord Object
Object -> Object -> Bool
Object -> Object -> Ordering
Object -> Object -> Object
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Object -> Object -> Object
$cmin :: Object -> Object -> Object
max :: Object -> Object -> Object
$cmax :: Object -> Object -> Object
>= :: Object -> Object -> Bool
$c>= :: Object -> Object -> Bool
> :: Object -> Object -> Bool
$c> :: Object -> Object -> Bool
<= :: Object -> Object -> Bool
$c<= :: Object -> Object -> Bool
< :: Object -> Object -> Bool
$c< :: Object -> Object -> Bool
compare :: Object -> Object -> Ordering
$ccompare :: Object -> Object -> Ordering
$cp1Ord :: Eq Object
Ord, Typeable, (forall x. Object -> Rep Object x)
-> (forall x. Rep Object x -> Object) -> Generic Object
forall x. Rep Object x -> Object
forall x. Object -> Rep Object x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Object x -> Object
$cfrom :: forall x. Object -> Rep Object x
Generic)

instance NFData Object