{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE StrictData #-}
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 (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
instance Arbitrary Object where
arbitrary :: Gen Object
arbitrary = (Int -> Gen Object) -> Gen Object
forall a. (Int -> Gen a) -> Gen a
Gen.sized ((Int -> Gen Object) -> Gen Object)
-> (Int -> Gen Object) -> Gen Object
forall a b. (a -> b) -> a -> b
$ \Int
n -> [Gen Object] -> Gen Object
forall a. [Gen a] -> Gen a
Gen.oneof
[ Object -> Gen Object
forall (f :: * -> *) a. Applicative f => a -> f a
pure Object
ObjectNil
, Bool -> Object
ObjectBool (Bool -> Object) -> Gen Bool -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Bool
forall a. Arbitrary a => Gen a
arbitrary
, Int64 -> Object
ObjectInt (Int64 -> Object) -> Gen Int64 -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int64
negatives
, Word64 -> Object
ObjectWord (Word64 -> Object) -> Gen Word64 -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word64
forall a. Arbitrary a => Gen a
arbitrary
, Float -> Object
ObjectFloat (Float -> Object) -> Gen Float -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Float
forall a. Arbitrary a => Gen a
arbitrary
, Double -> Object
ObjectDouble (Double -> Object) -> Gen Double -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Double
forall a. Arbitrary a => Gen a
arbitrary
, Text -> Object
ObjectStr (Text -> Object) -> Gen Text -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Text
T.pack (String -> Text) -> Gen String -> Gen Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen String
forall a. Arbitrary a => Gen a
arbitrary)
, ByteString -> Object
ObjectBin (ByteString -> Object) -> Gen ByteString -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Word8] -> ByteString
S.pack ([Word8] -> ByteString) -> Gen [Word8] -> Gen ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [Word8]
forall a. Arbitrary a => Gen a
arbitrary)
, [Object] -> Object
ObjectArray ([Object] -> Object) -> Gen [Object] -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Gen [Object] -> Gen [Object]
forall a. Int -> Gen a -> Gen a
Gen.resize (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2) Gen [Object]
forall a. Arbitrary a => Gen a
arbitrary
, [(Object, Object)] -> Object
ObjectMap ([(Object, Object)] -> Object)
-> Gen [(Object, Object)] -> Gen Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Gen [(Object, Object)] -> Gen [(Object, Object)]
forall a. Int -> Gen a -> Gen a
Gen.resize (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
4) Gen [(Object, Object)]
forall a. Arbitrary a => Gen a
arbitrary
, Word8 -> ByteString -> Object
ObjectExt (Word8 -> ByteString -> Object)
-> Gen Word8 -> Gen (ByteString -> Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word8
forall a. Arbitrary a => Gen a
arbitrary Gen (ByteString -> Object) -> Gen ByteString -> Gen Object
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([Word8] -> ByteString
S.pack ([Word8] -> ByteString) -> Gen [Word8] -> Gen ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [Word8]
forall a. Arbitrary a => Gen a
arbitrary)
]
where negatives :: Gen Int64
negatives = (Int64, Int64) -> Gen Int64
forall a. Random a => (a, a) -> Gen a
Gen.choose (Int64
forall a. Bounded a => a
minBound, -Int64
1)