{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE StrictData #-} {-# LANGUAGE Trustworthy #-} module Data.MessagePack.Arbitrary () where import qualified Data.ByteString as S import Data.MessagePack.Types (Object (..)) import qualified Data.Text as T import qualified Data.Vector as V import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import qualified Test.QuickCheck.Gen as Gen 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) , Vector Object -> Object ObjectArray (Vector Object -> Object) -> Gen (Vector Object) -> Gen Object forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ([Object] -> Vector Object forall a. [a] -> Vector a V.fromList ([Object] -> Vector Object) -> Gen [Object] -> Gen (Vector 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) , Vector (Object, Object) -> Object ObjectMap (Vector (Object, Object) -> Object) -> Gen (Vector (Object, Object)) -> Gen Object forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ([(Object, Object)] -> Vector (Object, Object) forall a. [a] -> Vector a V.fromList ([(Object, Object)] -> Vector (Object, Object)) -> Gen [(Object, Object)] -> Gen (Vector (Object, 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)