QuickCheck-GenT-0.1.0: A GenT monad transformer for QuickCheck library.

Safe HaskellNone

QuickCheck.GenT

Contents

Description

Most of the code is borrowed from the following mailing list discussion: http:haskell.1045720.n5.nabble.com/darcs-patch-GenT-monad-transformer-variant-of-Gen-QuickCheck-2-td3172136.html Therefor, credits go to Paul Johnson and Felix Martini.

Synopsis

Documentation

newtype GenT m a Source

Constructors

GenT 

Fields

unGenT :: StdGen -> Int -> m a
 

Instances

MonadTrans GenT 
Monad m => Monad (GenT m) 
Functor m => Functor (GenT m) 
(Functor m, Monad m) => Applicative (GenT m) 
MonadIO m => MonadIO (GenT m) 
(Applicative m, Monad m) => MonadGen (GenT m) 

runGenT :: GenT m a -> Gen (m a)Source

class (Applicative g, Monad g) => MonadGen g whereSource

Methods

liftGen :: Gen a -> g aSource

variant :: Integral n => n -> g a -> g aSource

sized :: (Int -> g a) -> g aSource

resize :: Int -> g a -> g aSource

choose :: Random a => (a, a) -> g aSource

Instances

var :: Integral n => n -> StdGen -> StdGenSource

Private variant-generating function. Converts an integer into a chain of (fst . split) and (snd . split) applications. Every integer (including negative ones) will give rise to a different random number generator in log2 n steps.

Common generator combinators

suchThat :: MonadGen m => m a -> (a -> Bool) -> m aSource

Generates a value that satisfies a predicate.

suchThatMaybe :: MonadGen m => m a -> (a -> Bool) -> m (Maybe a)Source

Tries to generate a value that satisfies a predicate.

oneof :: MonadGen m => [m a] -> m aSource

Randomly uses one of the given generators. The input list must be non-empty.

frequency :: MonadGen m => [(Int, m a)] -> m aSource

Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.

elements :: MonadGen m => [a] -> m aSource

Generates one of the given values. The input list must be non-empty.

growingElements :: MonadGen m => [a] -> m aSource

Takes a list of elements of increasing size, and chooses among an initial segment of the list. The size of this initial segment increases with the size parameter. The input list must be non-empty.

listOf :: MonadGen m => m a -> m [a]Source

Generates a list of random length. The maximum length depends on the size parameter.

listOf1 :: MonadGen m => m a -> m [a]Source

Generates a non-empty list of random length. The maximum length depends on the size parameter.

vectorOf :: MonadGen m => Int -> m a -> m [a]Source

Generates a list of the given length.