#ifndef NO_MULTI_PARAM_TYPE_CLASSES
#endif
#ifndef NO_NEWTYPE_DERIVING
#endif
module Test.QuickCheck.Modifiers
(
Blind(..)
, Fixed(..)
, OrderedList(..)
, NonEmptyList(..)
, Positive(..)
, NonZero(..)
, NonNegative(..)
, Smart(..)
, Shrink2(..)
, Shrinking(..)
, ShrinkState(..)
)
where
import Test.QuickCheck.Gen
import Test.QuickCheck.Arbitrary
import Data.List
( sort
)
newtype Blind a = Blind a
deriving ( Eq, Ord
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
)
instance Show (Blind a) where
show _ = "(*)"
instance Arbitrary a => Arbitrary (Blind a) where
arbitrary = Blind `fmap` arbitrary
shrink (Blind x) = [ Blind x' | x' <- shrink x ]
newtype Fixed a = Fixed a
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
)
instance Arbitrary a => Arbitrary (Fixed a) where
arbitrary = Fixed `fmap` arbitrary
newtype OrderedList a = Ordered [a]
deriving ( Eq, Ord, Show, Read )
instance (Ord a, Arbitrary a) => Arbitrary (OrderedList a) where
arbitrary = Ordered `fmap` orderedList
shrink (Ordered xs) =
[ Ordered xs'
| xs' <- shrink xs
, sort xs' == xs'
]
newtype NonEmptyList a = NonEmpty [a]
deriving ( Eq, Ord, Show, Read )
instance Arbitrary a => Arbitrary (NonEmptyList a) where
arbitrary = NonEmpty `fmap` (arbitrary `suchThat` (not . null))
shrink (NonEmpty xs) =
[ NonEmpty xs'
| xs' <- shrink xs
, not (null xs')
]
newtype Positive a = Positive a
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
)
instance (Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) where
arbitrary =
(Positive . abs) `fmap` (arbitrary `suchThat` (/= 0))
shrink (Positive x) =
[ Positive x'
| x' <- shrink x
, x' > 0
]
newtype NonZero a = NonZero a
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
)
instance (Num a, Ord a, Arbitrary a) => Arbitrary (NonZero a) where
arbitrary = fmap NonZero $ arbitrary `suchThat` (/= 0)
shrink (NonZero x) = [ NonZero x' | x' <- shrink x, x' /= 0 ]
newtype NonNegative a = NonNegative a
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
)
instance (Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) where
arbitrary =
frequency
[ (5, (NonNegative . abs) `fmap` arbitrary)
, (1, return (NonNegative 0))
]
shrink (NonNegative x) =
[ NonNegative x'
| x' <- shrink x
, x' >= 0
]
newtype Shrink2 a = Shrink2 a
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
)
instance Arbitrary a => Arbitrary (Shrink2 a) where
arbitrary =
Shrink2 `fmap` arbitrary
shrink (Shrink2 x) =
[ Shrink2 y | y <- shrink_x ] ++
[ Shrink2 z
| y <- shrink_x
, z <- shrink y
]
where
shrink_x = shrink x
data Smart a =
Smart Int a
instance Show a => Show (Smart a) where
showsPrec n (Smart _ x) = showsPrec n x
instance Arbitrary a => Arbitrary (Smart a) where
arbitrary =
do x <- arbitrary
return (Smart 0 x)
shrink (Smart i x) = take i' ys `ilv` drop i' ys
where
ys = [ Smart j y | (j,y) <- [0..] `zip` shrink x ]
i' = 0 `max` (i2)
[] `ilv` bs = bs
as `ilv` [] = as
(a:as) `ilv` (b:bs) = a : b : (as `ilv` bs)
#ifndef NO_MULTI_PARAM_TYPE_CLASSES
data Shrinking s a =
Shrinking s a
class ShrinkState s a where
shrinkInit :: a -> s
shrinkState :: a -> s -> [(a,s)]
instance Show a => Show (Shrinking s a) where
showsPrec n (Shrinking _ x) = showsPrec n x
instance (Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) where
arbitrary =
do x <- arbitrary
return (Shrinking (shrinkInit x) x)
shrink (Shrinking s x) =
[ Shrinking s' x'
| (x',s') <- shrinkState x s
]
#endif /* NO_MULTI_PARAM_TYPE_CLASSES */