safe-gen-1.0.1: Recursive Arbitrary instances without headaches
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.QuickCheck.SafeGen

Contents

Synopsis

Documentation

runSafeGen :: SafeGen a -> Gen a Source #

Run a SafeGen using the current context's size parameter. If the SafeGen value does not have a leaf within 20 layers, assume it has infinite recursion, and throw an exception.

runSafeGenNoCheck :: SafeGen a -> Gen a Source #

like runSafeGen, but doesn't first check if this generator can terminate.

gen :: Gen a -> SafeGen a Source #

Lift a SafeGen generator into SafeGen.

arb :: Arbitrary a => SafeGen a Source #

Convenient synonym for 'gen arbitrary'.

data SafeGen a Source #

SafeGen is a tree of SafeGen values, that automatically distributes the size parameter over its branches. To run/consume a tree, use runSafeGen. Branches are either product types (composed through the Applicative interface), or sum types composed using oneof or frequency.

Instances

Instances details
Applicative SafeGen Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Internal

Methods

pure :: a -> SafeGen a #

(<*>) :: SafeGen (a -> b) -> SafeGen a -> SafeGen b #

liftA2 :: (a -> b -> c) -> SafeGen a -> SafeGen b -> SafeGen c #

(*>) :: SafeGen a -> SafeGen b -> SafeGen b #

(<*) :: SafeGen a -> SafeGen b -> SafeGen a #

Functor SafeGen Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Internal

Methods

fmap :: (a -> b) -> SafeGen a -> SafeGen b #

(<$) :: a -> SafeGen b -> SafeGen a #

Arbitrary a => Arbitrary (SafeGen a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Internal

Methods

arbitrary :: Gen (SafeGen a) #

shrink :: SafeGen a -> [SafeGen a] #

oneof :: [SafeGen a] -> SafeGen a Source #

Pick one of these branches, with equal probability. Only branches shallower than the current size are considered.

frequency :: [(Int, SafeGen a)] -> SafeGen a Source #

Pick one of these branches, with weighted probability. Only branches shallower than the current size are considered.

Generics

class SafeArbitrary a where Source #

Like Arbitrary, but with SafeGen instead of Gen. In practice, you probably won't interface with this class directly other than deriving an instance when deriving Arbitrary via FromSafeArbitrary.

One exception might be when you're not happy with the way FromSafeArbitrary derives shrink, and you want to manually implement it. In that case, you can manually write arbitrary = runSafeGen safeArbitrary

Another example is when working with lazy infinite data, in which case you might want to remove the termination check using arbitrary = runSafeGenNoCheck safeArbitrary.

Minimal complete definition

Nothing

Methods

safeArbitrary :: SafeGen a Source #

default safeArbitrary :: (Generic a, GSafeArbitrary (Rep a)) => SafeGen a Source #

Instances

Instances details
SafeArbitrary PrintableString Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary UnicodeString Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary All Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Any Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CChar Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CClock Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CDouble Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CFloat Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CInt Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CIntMax Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CIntPtr Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CLLong Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CLong Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CPtrdiff Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CSChar Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CSUSeconds Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CShort Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CSigAtomic Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CSize Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CTime Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CUChar Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CUInt Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CUIntMax Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CUIntPtr Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CULLong Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CULong Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CUSeconds Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CUShort Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary CWchar Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Int16 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Int32 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Int64 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Int8 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Word16 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Word32 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Word64 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Word8 Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Ordering Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Integer Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary () Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Bool Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Char Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Double Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Float Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Int Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary Word Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (ZipList a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (Complex a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (Identity a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (First a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (Last a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (Dual a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (Product a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (Sum a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

Integral a => SafeArbitrary (Ratio a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (NonEmpty a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary (Maybe a) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

SafeArbitrary a => SafeArbitrary [a] Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

(SafeArbitrary a, SafeArbitrary b) => SafeArbitrary (Either a b) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

(SafeArbitrary a, SafeArbitrary b) => SafeArbitrary (a, b) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

Methods

safeArbitrary :: SafeGen (a, b) Source #

(SafeArbitrary a, SafeArbitrary b, SafeArbitrary c) => SafeArbitrary (a, b, c) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

Methods

safeArbitrary :: SafeGen (a, b, c) Source #

(SafeArbitrary a, SafeArbitrary b, SafeArbitrary c, SafeArbitrary d) => SafeArbitrary (a, b, c, d) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

Methods

safeArbitrary :: SafeGen (a, b, c, d) Source #

(SafeArbitrary a, SafeArbitrary b, SafeArbitrary c, SafeArbitrary d, SafeArbitrary e) => SafeArbitrary (a, b, c, d, e) Source # 
Instance details

Defined in Test.QuickCheck.SafeGen.Generic

Methods

safeArbitrary :: SafeGen (a, b, c, d, e) Source #

newtype FromSafeArbitrary a Source #

Intended to be used as a deriving conduit for Arbitrary from SafeArbitrary. This defines arbitrary as runSafeGen arbitrary, and shrink as genericShrink.

Constructors

FromSafeArbitrary a