quickcheck-transformer-0.3: A GenT monad transformer for QuickCheck library.

Safe HaskellSafe
LanguageHaskell2010

Test.QuickCheck.GenT

Contents

Description

Most of the code is borrowed from a mailing list discussion. Therefor, credits go to Paul Johnson and Felix Martini.

Synopsis

Documentation

newtype GenT m a Source #

Constructors

GenT 

Fields

Instances
MonadTrans GenT Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

lift :: Monad m => m a -> GenT m a #

Monad m => Monad (GenT m) Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

(>>=) :: GenT m a -> (a -> GenT m b) -> GenT m b #

(>>) :: GenT m a -> GenT m b -> GenT m b #

return :: a -> GenT m a #

fail :: String -> GenT m a #

Functor m => Functor (GenT m) Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

fmap :: (a -> b) -> GenT m a -> GenT m b #

(<$) :: a -> GenT m b -> GenT m a #

(Functor m, Monad m) => Applicative (GenT m) Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

pure :: a -> GenT m a #

(<*>) :: GenT m (a -> b) -> GenT m a -> GenT m b #

liftA2 :: (a -> b -> c) -> GenT m a -> GenT m b -> GenT m c #

(*>) :: GenT m a -> GenT m b -> GenT m b #

(<*) :: GenT m a -> GenT m b -> GenT m a #

MonadIO m => MonadIO (GenT m) Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

liftIO :: IO a -> GenT m a #

(Applicative m, Monad m) => MonadGen (GenT m) Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

liftGen :: Gen a -> GenT m a Source #

variant :: Integral n => n -> GenT m a -> GenT m a Source #

sized :: (Int -> GenT m a) -> GenT m a Source #

resize :: Int -> GenT m a -> GenT m a Source #

choose :: Random a => (a, a) -> GenT m a Source #

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

class (Applicative g, Monad g) => MonadGen g where Source #

Methods

liftGen :: Gen a -> g a Source #

variant :: Integral n => n -> g a -> g a Source #

sized :: (Int -> g a) -> g a Source #

resize :: Int -> g a -> g a Source #

choose :: Random a => (a, a) -> g a Source #

Instances
MonadGen Gen Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

liftGen :: Gen a -> Gen a Source #

variant :: Integral n => n -> Gen a -> Gen a Source #

sized :: (Int -> Gen a) -> Gen a Source #

resize :: Int -> Gen a -> Gen a Source #

choose :: Random a => (a, a) -> Gen a Source #

(Applicative m, Monad m) => MonadGen (GenT m) Source # 
Instance details

Defined in Test.QuickCheck.GenT

Methods

liftGen :: Gen a -> GenT m a Source #

variant :: Integral n => n -> GenT m a -> GenT m a Source #

sized :: (Int -> GenT m a) -> GenT m a Source #

resize :: Int -> GenT m a -> GenT m a Source #

choose :: Random a => (a, a) -> GenT m a Source #

var :: Integral n => n -> QCGen -> QCGen Source #

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 a Source #

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.

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.

Partial functions

oneof :: MonadGen m => [m a] -> m a Source #

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

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

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

elements :: MonadGen m => [a] -> m a Source #

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

growingElements :: MonadGen m => [a] -> m a Source #

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.

Non-partial functions resulting in Maybe

oneofMay :: MonadGen m => [m a] -> m (Maybe a) Source #

Randomly uses one of the given generators.

elementsMay :: MonadGen m => [a] -> m (Maybe a) Source #

Generates one of the given values.

growingElementsMay :: MonadGen m => [a] -> m (Maybe a) Source #

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.