#ifndef NO_GENERICS
#endif
#ifndef NO_SAFE_HASKELL
#endif
module Test.QuickCheck.Arbitrary
(
Arbitrary(..)
, CoArbitrary(..)
, arbitrarySizedIntegral
, arbitrarySizedNatural
, arbitraryBoundedIntegral
, arbitrarySizedBoundedIntegral
, arbitrarySizedFractional
, arbitraryBoundedRandom
, arbitraryBoundedEnum
#ifndef NO_GENERICS
, genericShrink
, subterms
, recursivelyShrink
, genericCoarbitrary
#endif
, shrinkNothing
, shrinkList
, shrinkIntegral
, shrinkRealFrac
, shrinkRealFracToInteger
, coarbitraryIntegral
, coarbitraryReal
, coarbitraryShow
, coarbitraryEnum
, (><)
, vector
, orderedList
, infiniteList
)
where
import Control.Applicative
import System.Random(Random)
import Test.QuickCheck.Gen
import Test.QuickCheck.Gen.Unsafe
import Data.Char
( chr
, ord
, isLower
, isUpper
, toLower
, isDigit
, isSpace
)
#ifndef NO_FIXED
import Data.Fixed
( Fixed
, HasResolution
)
#endif
#ifndef NO_NATURALS
import Numeric.Natural
#endif
import Data.Ratio
( Ratio
, (%)
, numerator
, denominator
)
import Data.Complex
( Complex((:+)) )
import Data.List
( sort
, nub
)
import Control.Monad
( liftM
, liftM2
, liftM3
, liftM4
, liftM5
)
import Data.Int(Int8, Int16, Int32, Int64)
import Data.Word(Word, Word8, Word16, Word32, Word64)
#ifndef NO_GENERICS
import GHC.Generics
#endif
class Arbitrary a where
arbitrary :: Gen a
arbitrary = error "no default generator"
shrink :: a -> [a]
shrink _ = []
#ifndef NO_GENERICS
genericShrink :: (Generic a, Arbitrary a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a]
genericShrink x = subterms x ++ recursivelyShrink x
recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a]
recursivelyShrink = map to . grecursivelyShrink . from
class RecursivelyShrink f where
grecursivelyShrink :: f a -> [f a]
instance (RecursivelyShrink f, RecursivelyShrink g) => RecursivelyShrink (f :*: g) where
grecursivelyShrink (x :*: y) =
[x' :*: y | x' <- grecursivelyShrink x] ++
[x :*: y' | y' <- grecursivelyShrink y]
instance (RecursivelyShrink f, RecursivelyShrink g) => RecursivelyShrink (f :+: g) where
grecursivelyShrink (L1 x) = map L1 (grecursivelyShrink x)
grecursivelyShrink (R1 x) = map R1 (grecursivelyShrink x)
instance RecursivelyShrink f => RecursivelyShrink (M1 i c f) where
grecursivelyShrink (M1 x) = map M1 (grecursivelyShrink x)
instance Arbitrary a => RecursivelyShrink (K1 i a) where
grecursivelyShrink (K1 x) = map K1 (shrink x)
instance RecursivelyShrink U1 where
grecursivelyShrink U1 = []
instance RecursivelyShrink V1 where
grecursivelyShrink _ = []
subterms :: (Generic a, Arbitrary a, GSubterms (Rep a) a) => a -> [a]
subterms = gSubterms . from
class GSubterms f a where
gSubterms :: f a -> [a]
instance GSubterms V1 a where
gSubterms _ = []
instance GSubterms U1 a where
gSubterms U1 = []
instance (GSubtermsIncl f a, GSubtermsIncl g a) => GSubterms (f :*: g) a where
gSubterms (l :*: r) = gSubtermsIncl l ++ gSubtermsIncl r
instance (GSubtermsIncl f a, GSubtermsIncl g a) => GSubterms (f :+: g) a where
gSubterms (L1 x) = gSubtermsIncl x
gSubterms (R1 x) = gSubtermsIncl x
instance GSubterms f a => GSubterms (M1 i c f) a where
gSubterms (M1 x) = gSubterms x
instance GSubterms (K1 i a) b where
gSubterms (K1 _) = []
class GSubtermsIncl f a where
gSubtermsIncl :: f a -> [a]
instance GSubtermsIncl V1 a where
gSubtermsIncl _ = []
instance GSubtermsIncl U1 a where
gSubtermsIncl U1 = []
instance (GSubtermsIncl f a, GSubtermsIncl g a) => GSubtermsIncl (f :*: g) a where
gSubtermsIncl (l :*: r) = gSubtermsIncl l ++ gSubtermsIncl r
instance (GSubtermsIncl f a, GSubtermsIncl g a) => GSubtermsIncl (f :+: g) a where
gSubtermsIncl (L1 x) = gSubtermsIncl x
gSubtermsIncl (R1 x) = gSubtermsIncl x
instance GSubtermsIncl f a => GSubtermsIncl (M1 i c f) a where
gSubtermsIncl (M1 x) = gSubtermsIncl x
instance Arbitrary a => GSubtermsIncl (K1 i a) a where
gSubtermsIncl (K1 x) = [x]
instance GSubtermsIncl (K1 i a) b where
gSubtermsIncl (K1 _) = []
#endif
instance (CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) where
arbitrary = promote (`coarbitrary` arbitrary)
instance Arbitrary () where
arbitrary = return ()
instance Arbitrary Bool where
arbitrary = choose (False,True)
shrink True = [False]
shrink False = []
instance Arbitrary Ordering where
arbitrary = elements [LT, EQ, GT]
shrink GT = [EQ, LT]
shrink LT = [EQ]
shrink EQ = []
instance Arbitrary a => Arbitrary (Maybe a) where
arbitrary = frequency [(1, return Nothing), (3, liftM Just arbitrary)]
shrink (Just x) = Nothing : [ Just x' | x' <- shrink x ]
shrink _ = []
instance (Arbitrary a, Arbitrary b) => Arbitrary (Either a b) where
arbitrary = oneof [liftM Left arbitrary, liftM Right arbitrary]
shrink (Left x) = [ Left x' | x' <- shrink x ]
shrink (Right y) = [ Right y' | y' <- shrink y ]
instance Arbitrary a => Arbitrary [a] where
arbitrary = sized $ \n ->
do k <- choose (0,n)
sequence [ arbitrary | _ <- [1..k] ]
shrink xs = shrinkList shrink xs
shrinkList :: (a -> [a]) -> [a] -> [[a]]
shrinkList shr xs = concat [ removes k n xs | k <- takeWhile (>0) (iterate (`div`2) n) ]
++ shrinkOne xs
where
n = length xs
shrinkOne [] = []
shrinkOne (x:xs) = [ x':xs | x' <- shr x ]
++ [ x:xs' | xs' <- shrinkOne xs ]
removes k n xs
| k > n = []
| null xs2 = [[]]
| otherwise = xs2 : map (xs1 ++) (removes k (nk) xs2)
where
xs1 = take k xs
xs2 = drop k xs
instance (Integral a, Arbitrary a) => Arbitrary (Ratio a) where
arbitrary = arbitrarySizedFractional
shrink = shrinkRealFracToInteger
instance (RealFloat a, Arbitrary a) => Arbitrary (Complex a) where
arbitrary = liftM2 (:+) arbitrary arbitrary
shrink (x :+ y) = [ x' :+ y | x' <- shrink x ] ++
[ x :+ y' | y' <- shrink y ]
#ifndef NO_FIXED
instance HasResolution a => Arbitrary (Fixed a) where
arbitrary = arbitrarySizedFractional
shrink = shrinkRealFrac
#endif
instance (Arbitrary a, Arbitrary b)
=> Arbitrary (a,b)
where
arbitrary = liftM2 (,) arbitrary arbitrary
shrink (x, y) =
[ (x', y) | x' <- shrink x ]
++ [ (x, y') | y' <- shrink y ]
instance (Arbitrary a, Arbitrary b, Arbitrary c)
=> Arbitrary (a,b,c)
where
arbitrary = liftM3 (,,) arbitrary arbitrary arbitrary
shrink (x, y, z) =
[ (x', y', z')
| (x', (y', z')) <- shrink (x, (y, z)) ]
instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d)
=> Arbitrary (a,b,c,d)
where
arbitrary = liftM4 (,,,) arbitrary arbitrary arbitrary arbitrary
shrink (w, x, y, z) =
[ (w', x', y', z')
| (w', (x', (y', z'))) <- shrink (w, (x, (y, z))) ]
instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e)
=> Arbitrary (a,b,c,d,e)
where
arbitrary = liftM5 (,,,,) arbitrary arbitrary arbitrary arbitrary arbitrary
shrink (v, w, x, y, z) =
[ (v', w', x', y', z')
| (v', (w', (x', (y', z')))) <- shrink (v, (w, (x, (y, z)))) ]
instance Arbitrary Integer where
arbitrary = arbitrarySizedIntegral
shrink = shrinkIntegral
#ifndef NO_NATURALS
instance Arbitrary Natural where
arbitrary = arbitrarySizedNatural
shrink = shrinkIntegral
#endif
instance Arbitrary Int where
arbitrary = arbitrarySizedIntegral
shrink = shrinkIntegral
instance Arbitrary Int8 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Int16 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Int32 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Int64 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Word where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Word8 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Word16 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Word32 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Word64 where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
instance Arbitrary Char where
arbitrary = chr `fmap` oneof [choose (0,127), choose (0,255)]
shrink c = filter (<. c) $ nub
$ ['a','b','c']
++ [ toLower c | isUpper c ]
++ ['A','B','C']
++ ['1','2','3']
++ [' ','\n']
where
a <. b = stamp a < stamp b
stamp a = ( (not (isLower a)
, not (isUpper a)
, not (isDigit a))
, (not (a==' ')
, not (isSpace a)
, a)
)
instance Arbitrary Float where
arbitrary = arbitrarySizedFractional
shrink = shrinkRealFrac
instance Arbitrary Double where
arbitrary = arbitrarySizedFractional
shrink = shrinkRealFrac
arbitrarySizedIntegral :: Integral a => Gen a
arbitrarySizedIntegral =
sized $ \n ->
inBounds fromInteger (choose (toInteger n, toInteger n))
arbitrarySizedNatural :: Integral a => Gen a
arbitrarySizedNatural =
sized $ \n ->
inBounds fromInteger (choose (0, toInteger n))
inBounds :: Integral a => (Integer -> a) -> Gen Integer -> Gen a
inBounds fi g = fmap fi (g `suchThat` (\x -> toInteger (fi x) == x))
arbitrarySizedFractional :: Fractional a => Gen a
arbitrarySizedFractional =
sized $ \n ->
let n' = toInteger n in
do a <- choose ((n') * precision, n' * precision)
b <- choose (1, precision)
return (fromRational (a % b))
where
precision = 9999999999999 :: Integer
withBounds :: Bounded a => (a -> a -> Gen a) -> Gen a
withBounds k = k minBound maxBound
arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a
arbitraryBoundedIntegral =
withBounds $ \mn mx ->
do n <- choose (toInteger mn, toInteger mx)
return (fromInteger n)
arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a
arbitraryBoundedRandom = choose (minBound,maxBound)
arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum =
withBounds $ \mn mx ->
do n <- choose (fromEnum mn, fromEnum mx)
return (toEnum n)
arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a
arbitrarySizedBoundedIntegral =
withBounds $ \mn mx ->
sized $ \s ->
do let bits n | n `quot` 2 == 0 = 0
| otherwise = 1 + bits (n `quot` 2)
k = 2^(s*(bits mn `max` bits mx `max` 40) `div` 100)
n <- choose (toInteger mn `max` (k), toInteger mx `min` k)
return (fromInteger n)
shrinkNothing :: a -> [a]
shrinkNothing _ = []
shrinkIntegral :: Integral a => a -> [a]
shrinkIntegral x =
nub $
[ x
| x < 0, x > x
] ++
[ x'
| x' <- takeWhile (<< x) (0:[ x i | i <- tail (iterate (`quot` 2) x) ])
]
where
a << b = case (a >= 0, b >= 0) of
(True, True) -> a < b
(False, False) -> a > b
(True, False) -> a + b < 0
(False, True) -> a + b > 0
shrinkRealFracToInteger :: RealFrac a => a -> [a]
shrinkRealFracToInteger x =
nub $
[ x
| x < 0
] ++
map fromInteger (shrinkIntegral (truncate x))
shrinkRealFrac :: RealFrac a => a -> [a]
shrinkRealFrac x =
nub $
shrinkRealFracToInteger x ++
[ x x'
| x' <- take 20 (iterate (/ 2) x)
, (x x') << x ]
where
a << b = abs a < abs b
#ifndef NO_GENERICS
#else
#endif
class CoArbitrary a where
coarbitrary :: a -> Gen b -> Gen b
#ifndef NO_GENERICS
default coarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b
coarbitrary = genericCoarbitrary
genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b
genericCoarbitrary = gCoarbitrary . from
class GCoArbitrary f where
gCoarbitrary :: f a -> Gen b -> Gen b
instance GCoArbitrary U1 where
gCoarbitrary U1 = id
instance (GCoArbitrary f, GCoArbitrary g) => GCoArbitrary (f :*: g) where
gCoarbitrary (l :*: r) = gCoarbitrary l . gCoarbitrary r
instance (GCoArbitrary f, GCoArbitrary g) => GCoArbitrary (f :+: g) where
gCoarbitrary (L1 x) = variant 0 . gCoarbitrary x
gCoarbitrary (R1 x) = variant 1 . gCoarbitrary x
instance GCoArbitrary f => GCoArbitrary (M1 i c f) where
gCoarbitrary (M1 x) = gCoarbitrary x
instance CoArbitrary a => GCoArbitrary (K1 i a) where
gCoarbitrary (K1 x) = coarbitrary x
#endif
(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> (Gen a -> Gen a)
(><) = (.)
instance (Arbitrary a, CoArbitrary b) => CoArbitrary (a -> b) where
coarbitrary f gen =
do xs <- arbitrary
coarbitrary (map f xs) gen
instance CoArbitrary () where
coarbitrary _ = id
instance CoArbitrary Bool where
coarbitrary False = variant 0
coarbitrary True = variant 1
instance CoArbitrary Ordering where
coarbitrary GT = variant 0
coarbitrary EQ = variant 1
coarbitrary LT = variant 2
instance CoArbitrary a => CoArbitrary (Maybe a) where
coarbitrary Nothing = variant 0
coarbitrary (Just x) = variant 1 . coarbitrary x
instance (CoArbitrary a, CoArbitrary b) => CoArbitrary (Either a b) where
coarbitrary (Left x) = variant 0 . coarbitrary x
coarbitrary (Right y) = variant 1 . coarbitrary y
instance CoArbitrary a => CoArbitrary [a] where
coarbitrary [] = variant 0
coarbitrary (x:xs) = variant 1 . coarbitrary (x,xs)
instance (Integral a, CoArbitrary a) => CoArbitrary (Ratio a) where
coarbitrary r = coarbitrary (numerator r,denominator r)
#ifndef NO_FIXED
instance HasResolution a => CoArbitrary (Fixed a) where
coarbitrary = coarbitraryReal
#endif
instance (RealFloat a, CoArbitrary a) => CoArbitrary (Complex a) where
coarbitrary (x :+ y) = coarbitrary x . coarbitrary y
instance (CoArbitrary a, CoArbitrary b)
=> CoArbitrary (a,b)
where
coarbitrary (x,y) = coarbitrary x
. coarbitrary y
instance (CoArbitrary a, CoArbitrary b, CoArbitrary c)
=> CoArbitrary (a,b,c)
where
coarbitrary (x,y,z) = coarbitrary x
. coarbitrary y
. coarbitrary z
instance (CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d)
=> CoArbitrary (a,b,c,d)
where
coarbitrary (x,y,z,v) = coarbitrary x
. coarbitrary y
. coarbitrary z
. coarbitrary v
instance (CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d, CoArbitrary e)
=> CoArbitrary (a,b,c,d,e)
where
coarbitrary (x,y,z,v,w) = coarbitrary x
. coarbitrary y
. coarbitrary z
. coarbitrary v
. coarbitrary w
instance CoArbitrary Integer where
coarbitrary = coarbitraryIntegral
#ifndef NO_NATURALS
instance CoArbitrary Natural where
coarbitrary = coarbitraryIntegral
#endif
instance CoArbitrary Int where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Int8 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Int16 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Int32 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Int64 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Word where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Word8 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Word16 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Word32 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Word64 where
coarbitrary = coarbitraryIntegral
instance CoArbitrary Char where
coarbitrary = coarbitrary . ord
instance CoArbitrary Float where
coarbitrary = coarbitraryReal
instance CoArbitrary Double where
coarbitrary = coarbitraryReal
coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b
coarbitraryIntegral = variant
coarbitraryReal :: Real a => a -> Gen b -> Gen b
coarbitraryReal x = coarbitrary (toRational x)
coarbitraryShow :: Show a => a -> Gen b -> Gen b
coarbitraryShow x = coarbitrary (show x)
coarbitraryEnum :: Enum a => a -> Gen b -> Gen b
coarbitraryEnum = variant . fromEnum
vector :: Arbitrary a => Int -> Gen [a]
vector k = vectorOf k arbitrary
orderedList :: (Ord a, Arbitrary a) => Gen [a]
orderedList = sort `fmap` arbitrary
infiniteList :: Arbitrary a => Gen [a]
infiniteList = infiniteListOf arbitrary