{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
module Data.MessagePack.Types.Object
( Object (..)
) where
import Control.Applicative ((<$>), (<*>))
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 Data.Word (Word64, Word8)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Test.QuickCheck.Gen as Gen
data Object
= ObjectNil
| ObjectBool !Bool
| ObjectInt {-# UNPACK #-} !Int64
| ObjectWord {-# UNPACK #-} !Word64
| ObjectFloat {-# UNPACK #-} !Float
| ObjectDouble {-# UNPACK #-} !Double
| ObjectStr !T.Text
| ObjectBin !S.ByteString
| ObjectArray ![Object]
| ObjectMap ![(Object, Object)]
| ObjectExt {-# UNPACK #-} !Word8 !S.ByteString
deriving (Read, Show, Eq, Ord, Typeable, Generic)
instance NFData Object
instance Arbitrary Object where
arbitrary = Gen.sized $ \n -> Gen.oneof
[ pure ObjectNil
, ObjectBool <$> arbitrary
, ObjectInt <$> negatives
, ObjectWord <$> arbitrary
, ObjectFloat <$> arbitrary
, ObjectDouble <$> arbitrary
, ObjectStr <$> (T.pack <$> arbitrary)
, ObjectBin <$> (S.pack <$> arbitrary)
, ObjectArray <$> Gen.resize (n `div` 2) arbitrary
, ObjectMap <$> Gen.resize (n `div` 4) arbitrary
, ObjectExt <$> arbitrary <*> (S.pack <$> arbitrary)
]
where negatives = Gen.choose (minBound, -1)