quickcheck-dynamic-3.4.1: A library for stateful property-based testing
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.QuickCheck.DynamicLogic.Internal

Synopsis

Documentation

newtype DynFormula s Source #

A DynFormula may depend on the QuickCheck size parameter

Constructors

DynFormula 

Fields

data DynLogic s Source #

Base Dynamic logic formulae language. Formulae are parameterised over the type of state s to which they apply. A DynLogic value cannot be constructed directly, one has to use the various "smart constructors" provided, see the Building formulae section.

Constructors

EmptySpec

False

Stop

True

AfterAny (DynPred s)

After any action the predicate should hold

Alt ChoiceType (DynLogic s) (DynLogic s)

Choice (angelic or demonic)

Stopping (DynLogic s)

Prefer this branch if trying to stop.

forall a.(Eq (Action s a), Show (Action s a), Typeable a) => After (ActionWithPolarity s a) (Var a -> DynPred s)

After a specific action the predicate should hold

Error String (DynPred s) 
Weight Double (DynLogic s)

Adjust the probability of picking a branch

forall a.QuantifyConstraints a => ForAll (Quantification a) (a -> DynLogic s)

Generating a random value

Monitor (Property -> Property) (DynLogic s)

Apply a QuickCheck property modifier (like tabulate or collect)

data ChoiceType Source #

Constructors

Angelic 
Demonic 

Instances

Instances details
Show ChoiceType Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

Eq ChoiceType Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

Building formulae

ignore :: DynFormula s Source #

Ignore this formula, i.e. backtrack and try something else. forAllScripts ignore (const True) will discard all test cases (equivalent to False ==> True).

passTest :: DynFormula s Source #

True for DL formulae.

afterAny :: (Annotated s -> DynFormula s) -> DynFormula s Source #

Given f must be True given any state.

afterPolar :: (Typeable a, Eq (Action s a), Show (Action s a)) => ActionWithPolarity s a -> (Var a -> Annotated s -> DynFormula s) -> DynFormula s Source #

after :: (Typeable a, Eq (Action s a), Show (Action s a)) => Action s a -> (Var a -> Annotated s -> DynFormula s) -> DynFormula s Source #

Given f must be True after some action. f is passed the state resulting from executing the Action.

afterNegative :: (Typeable a, Eq (Action s a), Show (Action s a)) => Action s a -> (Annotated s -> DynFormula s) -> DynFormula s Source #

Given f must be True after some negative action. f is passed the state resulting from executing the Action as a negative action.

(|||) :: DynFormula s -> DynFormula s -> DynFormula s Source #

Disjunction for DL formulae. Is True if either formula is True. The choice is angelic, ie. it is always made by the "caller". This is mostly important in case a test is Stuck.

forAllQ :: Quantifiable q => q -> (Quantifies q -> DynFormula s) -> DynFormula s Source #

First-order quantification of variables. Formula f is True iff. it is True for all possible values of q. The underlying framework will generate values of q and check the formula holds for those values. Quantifiable values are thus values that can be generated and checked and the Quantify module defines basic combinators to build those from building blocks.

weight :: Double -> DynFormula s -> DynFormula s Source #

Adjust weight for selecting formula. This is mostly useful in relation with (|||) combinator, in order to tweak the priority for generating the next step(s) of the test that matches the formula.

withSize :: (Int -> DynFormula s) -> DynFormula s Source #

Get the current QuickCheck size parameter.

toStop :: DynFormula s -> DynFormula s Source #

Prioritise doing this if we are trying to stop generation.

done :: Annotated s -> DynFormula s Source #

Successfully ends the test.

errorDL :: String -> DynFormula s Source #

Ends test with given error message.

monitorDL :: (Property -> Property) -> DynFormula s -> DynFormula s Source #

Embed QuickCheck's monitoring functions (eg. label, tabulate) in a formula. This is useful to improve the reporting from test execution, esp. in the case of failures.

always :: (Annotated s -> DynFormula s) -> Annotated s -> DynFormula s Source #

Formula should hold at any state. In effect this leads to exploring alternatives from a given state s and ensuring formula holds in all those states.

data Witnesses r where Source #

Constructors

Do :: r -> Witnesses r 
Witness :: QuantifyConstraints a => a -> Witnesses r -> Witnesses r 

Instances

Instances details
Foldable Witnesses Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

Methods

fold :: Monoid m => Witnesses m -> m #

foldMap :: Monoid m => (a -> m) -> Witnesses a -> m #

foldMap' :: Monoid m => (a -> m) -> Witnesses a -> m #

foldr :: (a -> b -> b) -> b -> Witnesses a -> b #

foldr' :: (a -> b -> b) -> b -> Witnesses a -> b #

foldl :: (b -> a -> b) -> b -> Witnesses a -> b #

foldl' :: (b -> a -> b) -> b -> Witnesses a -> b #

foldr1 :: (a -> a -> a) -> Witnesses a -> a #

foldl1 :: (a -> a -> a) -> Witnesses a -> a #

toList :: Witnesses a -> [a] #

null :: Witnesses a -> Bool #

length :: Witnesses a -> Int #

elem :: Eq a => a -> Witnesses a -> Bool #

maximum :: Ord a => Witnesses a -> a #

minimum :: Ord a => Witnesses a -> a #

sum :: Num a => Witnesses a -> a #

product :: Num a => Witnesses a -> a #

Traversable Witnesses Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Witnesses a -> f (Witnesses b) #

sequenceA :: Applicative f => Witnesses (f a) -> f (Witnesses a) #

mapM :: Monad m => (a -> m b) -> Witnesses a -> m (Witnesses b) #

sequence :: Monad m => Witnesses (m a) -> m (Witnesses a) #

Functor Witnesses Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

Methods

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

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

Show r => Show (Witnesses r) Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

Eq r => Eq (Witnesses r) Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

Methods

(==) :: Witnesses r -> Witnesses r -> Bool #

(/=) :: Witnesses r -> Witnesses r -> Bool #

pattern Witnesses :: Witnesses () -> r -> Witnesses r Source #

newtype TestSequence s Source #

Constructors

TestSeq (Witnesses (TestContinuation s)) 

Instances

Instances details
StateModel s => Show (TestSequence s) Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

StateModel s => Eq (TestSequence s) Source # 
Instance details

Defined in Test.QuickCheck.DynamicLogic.Internal

pattern TestSeqWitness :: () => forall a. QuantifyConstraints a => a -> TestSequence s -> TestSequence s Source #

class StateModel s => DynLogicModel s where Source #

Restricted calls are not generated by AfterAny; they are included in tests explicitly using After in order to check specific properties at controlled times, so they are likely to fail if invoked at other times.

Minimal complete definition

Nothing

Methods

restricted :: Action s a -> Bool Source #

Generate Properties

forAllScripts :: (DynLogicModel s, Testable a) => DynFormula s -> (Actions s -> a) -> Property Source #

Simplest "execution" function for DynFormula. Turns a given a DynFormula paired with an interpreter function to produce some result from an

forAllUniqueScripts :: (DynLogicModel s, Testable a) => Annotated s -> DynFormula s -> (Actions s -> a) -> Property Source #

Property function suitable for formulae without choice.

forAllMappedScripts :: (DynLogicModel s, Testable a) => (rep -> DynLogicTest s) -> (DynLogicTest s -> rep) -> DynFormula s -> (Actions s -> a) -> Property Source #

Creates a Property from DynFormula with some specialised isomorphism for shrinking purpose.

generate :: (Monad m, DynLogicModel s) => (Annotated s -> Int -> DynLogic s -> m (NextStep s)) -> DynLogic s -> Int -> Annotated s -> Int -> m (DynLogicTest s) Source #

nextSteps' :: Monad m => (forall a. Quantification a -> m a) -> DynLogic s -> m [(Double, Witnesses (DynLogic s))] Source #

chooseOneOf :: [(Double, a)] -> Gen a Source #

keepTryingUntil :: Int -> Gen a -> (a -> Bool) -> Gen (Maybe a) Source #

shrinkWitness :: (StateModel s, Typeable a) => DynLogic s -> a -> [a] Source #

stepDLW :: forall s a. (DynLogicModel s, Typeable a) => DynLogic s -> a -> [DynLogic s] Source #

stepDLWitness :: forall a s. (DynLogicModel s, Typeable a) => DynLogic s -> a -> DynLogic s Source #

unfailDLTest :: DynLogicModel s => DynLogic s -> DynLogicTest s -> DynLogicTest s Source #

If failed, return the prefix up to the failure. Also prunes the test in case the model has changed.