less-arbitrary-0.1.8.0: Linear time testing with variant of Arbitrary class that always terminates.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.LessArbitrary

Synopsis

Documentation

class StartingState s => LessArbitrary s a where Source #

Minimal complete definition

Nothing

Methods

lessArbitrary :: CostGen s a Source #

default lessArbitrary :: (Generic a, GLessArbitrary s (Rep a)) => CostGen s a Source #

Instances

Instances details
StartingState s => LessArbitrary s Scientific Source # 
Instance details

Defined in Test.LessArbitrary

StartingState s => LessArbitrary s Integer Source # 
Instance details

Defined in Test.LessArbitrary

StartingState s => LessArbitrary s Bool Source # 
Instance details

Defined in Test.LessArbitrary

StartingState s => LessArbitrary s Char Source # 
Instance details

Defined in Test.LessArbitrary

StartingState s => LessArbitrary s Double Source # 
Instance details

Defined in Test.LessArbitrary

StartingState s => LessArbitrary s Int Source # 
Instance details

Defined in Test.LessArbitrary

(LessArbitrary s k, Ord k) => LessArbitrary s (Set k) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

lessArbitrary :: CostGen s (Set k) Source #

LessArbitrary s a => LessArbitrary s (Vector a) Source # 
Instance details

Defined in Test.LessArbitrary

LessArbitrary s a => LessArbitrary s [a] Source # 
Instance details

Defined in Test.LessArbitrary

Methods

lessArbitrary :: CostGen s [a] Source #

(LessArbitrary s k, Eq k, Ord k, Hashable k, LessArbitrary s v) => LessArbitrary s (HashMap k v) Source # 
Instance details

Defined in Test.LessArbitrary

(LessArbitrary s k, LessArbitrary s v) => LessArbitrary s (k, v) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

lessArbitrary :: CostGen s (k, v) Source #

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

budgetChoose :: CostGen s Int Source #

Choose but only up to the budget (for array and list sizes)

newtype CostGen s a Source #

Constructors

CostGen 

Fields

Instances

Instances details
MonadState s (CostGen s) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

get :: CostGen s s #

put :: s -> CostGen s () #

state :: (s -> (a, s)) -> CostGen s a #

MonadFix (CostGen s) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

mfix :: (a -> CostGen s a) -> CostGen s a #

Applicative (CostGen s) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

pure :: a -> CostGen s a #

(<*>) :: CostGen s (a -> b) -> CostGen s a -> CostGen s b #

liftA2 :: (a -> b -> c) -> CostGen s a -> CostGen s b -> CostGen s c #

(*>) :: CostGen s a -> CostGen s b -> CostGen s b #

(<*) :: CostGen s a -> CostGen s b -> CostGen s a #

Functor (CostGen s) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

fmap :: (a -> b) -> CostGen s a -> CostGen s b #

(<$) :: a -> CostGen s b -> CostGen s a #

Monad (CostGen s) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

(>>=) :: CostGen s a -> (a -> CostGen s b) -> CostGen s b #

(>>) :: CostGen s a -> CostGen s b -> CostGen s b #

return :: a -> CostGen s a #

(Testable a, LessArbitrary s a) => Testable (CostGen s a) Source # 
Instance details

Defined in Test.LessArbitrary

Methods

property :: CostGen s a -> Property #

propertyForAllShrinkShow :: Gen a0 -> (a0 -> [a0]) -> (a0 -> [String]) -> (a0 -> CostGen s a) -> Property #

(<$$$>) :: (a -> b) -> CostGen s a -> CostGen s b Source #

fasterArbitrary :: forall s a. LessArbitrary s a => Gen a Source #

genericLessArbitrary :: (Generic a, GLessArbitrary s (Rep a)) => CostGen s a Source #

genericLessArbitraryMonoid :: (Generic a, GLessArbitrary s (Rep a), Monoid a) => CostGen s a Source #

withCost :: forall s a. StartingState s => Int -> CostGen s a -> Gen a Source #

elements :: [a] -> CostGen s a Source #

forAll :: CostGen s a -> (a -> CostGen s b) -> CostGen s b Source #

class StartingState s where Source #

Methods

startingState :: s Source #

Instances

Instances details
StartingState () Source # 
Instance details

Defined in Test.LessArbitrary

Methods

startingState :: () Source #