{-# LANGUAGE CPP #-}
#ifndef NO_ST_MONAD
{-# LANGUAGE Rank2Types #-}
#endif
module Test.QuickCheck.Gen where
import System.Random
( Random
, random
, randomR
, split
)
import Control.Monad
( ap
, replicateM
, filterM
)
import Control.Monad.Fix
( MonadFix(..) )
import Control.Applicative
( Applicative(..) )
import Test.QuickCheck.Random
import Data.List
import Data.Ord
import Data.Maybe
#ifndef NO_SPLITMIX
import System.Random.SplitMix(bitmaskWithRejection64', SMGen, nextInteger)
#endif
import Data.Word
import Data.Int
import Data.Bits
import Control.Applicative
newtype Gen a = MkGen{
unGen :: QCGen -> Int -> a
}
instance Functor Gen where
fmap f (MkGen h) =
MkGen (\r n -> f (h r n))
instance Applicative Gen where
pure x =
MkGen (\_ _ -> x)
(<*>) = ap
#ifndef NO_EXTRA_METHODS_IN_APPLICATIVE
_ *> m = m
m <* _ = m
#endif
instance Monad Gen where
return = pure
MkGen m >>= k =
MkGen (\r n ->
case split r of
(r1, r2) ->
let MkGen m' = k (m r1 n)
in m' r2 n
)
(>>) = (*>)
instance MonadFix Gen where
mfix f =
MkGen $ \r n ->
let a = unGen (f a) r n
in a
variant :: Integral n => n -> Gen a -> Gen a
variant k (MkGen g) = MkGen (\r n -> g (integerVariant (toInteger k) $! r) n)
sized :: (Int -> Gen a) -> Gen a
sized f = MkGen (\r n -> let MkGen m = f n in m r n)
getSize :: Gen Int
getSize = sized pure
resize :: Int -> Gen a -> Gen a
resize n _ | n < 0 = error "Test.QuickCheck.resize: negative size"
resize n (MkGen g) = MkGen (\r _ -> g r n)
scale :: (Int -> Int) -> Gen a -> Gen a
scale f g = sized (\n -> resize (f n) g)
choose :: Random a => (a,a) -> Gen a
choose rng = MkGen (\r _ -> let (x,_) = randomR rng r in x)
chooseAny :: Random a => Gen a
chooseAny = MkGen (\r _ -> let (x,_) = random r in x)
chooseEnum :: Enum a => (a, a) -> Gen a
chooseEnum (lo, hi) =
fmap toEnum (chooseInt (fromEnum lo, fromEnum hi))
chooseInt :: (Int, Int) -> Gen Int
chooseInt = chooseBoundedIntegral
{-# INLINEABLE chooseBoundedIntegral #-}
chooseBoundedIntegral :: (Bounded a, Integral a) => (a, a) -> Gen a
chooseBoundedIntegral (lo, hi)
#ifndef NO_SPLITMIX
| toInteger mn >= toInteger (minBound :: Int64) &&
toInteger mx <= toInteger (maxBound :: Int64) =
fmap fromIntegral (chooseInt64 (fromIntegral lo, fromIntegral hi))
| toInteger mn >= toInteger (minBound :: Word64) &&
toInteger mx <= toInteger (maxBound :: Word64) =
fmap fromIntegral (chooseWord64 (fromIntegral lo, fromIntegral hi))
#endif
| otherwise =
fmap fromInteger (chooseInteger (toInteger lo, toInteger hi))
#ifndef NO_SPLITMIX
where
mn = minBound `asTypeOf` lo
mx = maxBound `asTypeOf` hi
#endif
chooseInteger :: (Integer, Integer) -> Gen Integer
#ifdef NO_SPLITMIX
chooseInteger = choose
#else
chooseInteger (lo, hi)
| lo >= toInteger (minBound :: Int64) && lo <= toInteger (maxBound :: Int64) &&
hi >= toInteger (minBound :: Int64) && hi <= toInteger (maxBound :: Int64) =
fmap toInteger (chooseInt64 (fromInteger lo, fromInteger hi))
| lo >= toInteger (minBound :: Word64) && lo <= toInteger (maxBound :: Word64) &&
hi >= toInteger (minBound :: Word64) && hi <= toInteger (maxBound :: Word64) =
fmap toInteger (chooseWord64 (fromInteger lo, fromInteger hi))
| otherwise = MkGen $ \(QCGen g) _ -> fst (nextInteger lo hi g)
chooseWord64 :: (Word64, Word64) -> Gen Word64
chooseWord64 (lo, hi)
| lo <= hi = chooseWord64' (lo, hi)
| otherwise = chooseWord64' (hi, lo)
where
chooseWord64' :: (Word64, Word64) -> Gen Word64
chooseWord64' (lo, hi) =
fmap (+ lo) (chooseUpTo (hi - lo))
chooseInt64 :: (Int64, Int64) -> Gen Int64
chooseInt64 (lo, hi)
| lo <= hi = chooseInt64' (lo, hi)
| otherwise = chooseInt64' (hi, lo)
where
chooseInt64' :: (Int64, Int64) -> Gen Int64
chooseInt64' (lo, hi) = do
w <- chooseUpTo (fromIntegral hi - fromIntegral lo)
return (fromIntegral (w + fromIntegral lo))
chooseUpTo :: Word64 -> Gen Word64
chooseUpTo n =
MkGen $ \(QCGen g) _ ->
fst (bitmaskWithRejection64' n g)
#endif
generate :: Gen a -> IO a
generate (MkGen g) =
do r <- newQCGen
return (g r 30)
sample' :: Gen a -> IO [a]
sample' g =
generate (sequence [ resize n g | n <- [0,2..20] ])
sample :: Show a => Gen a -> IO ()
sample g =
do cases <- sample' g
mapM_ print cases
suchThat :: Gen a -> (a -> Bool) -> Gen a
gen `suchThat` p =
do mx <- gen `suchThatMaybe` p
case mx of
Just x -> return x
Nothing -> sized (\n -> resize (n+1) (gen `suchThat` p))
suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b
gen `suchThatMap` f =
fmap fromJust $ fmap f gen `suchThat` isJust
suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)
gen `suchThatMaybe` p = sized (\n -> try n (2*n))
where
try m n
| m > n = return Nothing
| otherwise = do
x <- resize m gen
if p x then return (Just x) else try (m+1) n
oneof :: [Gen a] -> Gen a
oneof [] = error "QuickCheck.oneof used with empty list"
oneof gs = chooseInt (0,length gs - 1) >>= (gs !!)
frequency :: [(Int, Gen a)] -> Gen a
frequency [] = error "QuickCheck.frequency used with empty list"
frequency xs
| any (< 0) (map fst xs) =
error "QuickCheck.frequency: negative weight"
| all (== 0) (map fst xs) =
error "QuickCheck.frequency: all weights were zero"
frequency xs0 = chooseInt (1, tot) >>= (`pick` xs0)
where
tot = sum (map fst xs0)
pick n ((k,x):xs)
| n <= k = x
| otherwise = pick (n-k) xs
pick _ _ = error "QuickCheck.pick used with empty list"
elements :: [a] -> Gen a
elements [] = error "QuickCheck.elements used with empty list"
elements xs = (xs !!) `fmap` chooseInt (0, length xs - 1)
sublistOf :: [a] -> Gen [a]
sublistOf xs = filterM (\_ -> chooseEnum (False, True)) xs
shuffle :: [a] -> Gen [a]
shuffle xs = do
ns <- vectorOf (length xs) (chooseInt (minBound :: Int, maxBound))
return (map snd (sortBy (comparing fst) (zip ns xs)))
growingElements :: [a] -> Gen a
growingElements [] = error "QuickCheck.growingElements used with empty list"
growingElements xs = sized $ \n -> elements (take (1 `max` size n) xs)
where
k = length xs
mx = 100
log' = round . log . toDouble
size n = (log' n + 1) * k `div` log' mx
toDouble = fromIntegral :: Int -> Double
listOf :: Gen a -> Gen [a]
listOf gen = sized $ \n ->
do k <- chooseInt (0,n)
vectorOf k gen
listOf1 :: Gen a -> Gen [a]
listOf1 gen = sized $ \n ->
do k <- chooseInt (1,1 `max` n)
vectorOf k gen
vectorOf :: Int -> Gen a -> Gen [a]
vectorOf = replicateM
infiniteListOf :: Gen a -> Gen [a]
infiniteListOf gen = sequence (repeat gen)