quickcheck-higherorder-0.1.0.1: QuickCheck extension for higher-order properties
Safe HaskellNone
LanguageHaskell2010

Test.QuickCheck.HigherOrder

Description

QuickCheck extension for properties of higher-order values.

See the README for an introduction.

Synopsis

Constructible values

class (Arbitrary (Repr a), Show (Repr a)) => Constructible a where Source #

A Constructible type is associated with a type of "finite descriptions" that can be generated, shown (e.g., as counterexamples in QuickCheck), and interpreted as values. This enhances Arbitrary and Show used by vanilla QuickCheck.

The main motivating example is the type of functions, which can be finitely represented by the type (:->) (see also Test.Fun).

It turns out we can define Constructible for just about anything except IO (for now...).

Associated Types

type Repr a Source #

The observable representation of a value.

type Repr a = a

Methods

fromRepr :: Repr a -> a Source #

Interpret a representation as a value.

Instances

Instances details
Constructible Bool Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Bool Source #

Methods

fromRepr :: Repr Bool -> Bool Source #

Constructible Char Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Char Source #

Methods

fromRepr :: Repr Char -> Char Source #

Constructible Double Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Double Source #

Constructible Int Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Int Source #

Methods

fromRepr :: Repr Int -> Int Source #

Constructible Integer Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Integer Source #

Constructible Ordering Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Ordering Source #

Constructible Word Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Word Source #

Methods

fromRepr :: Repr Word -> Word Source #

Constructible () Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr () Source #

Methods

fromRepr :: Repr () -> () Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr [a] Source #

Methods

fromRepr :: Repr [a] -> [a] Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr (Maybe a) Source #

Methods

fromRepr :: Repr (Maybe a) -> Maybe a Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr (Identity a) Source #

Methods

fromRepr :: Repr (Identity a) -> Identity a Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr (Sum a) Source #

Methods

fromRepr :: Repr (Sum a) -> Sum a Source #

(CoArbitrary Gen a, Constructible b) => Constructible (a -> b) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Function

Associated Types

type Repr (a -> b) Source #

Methods

fromRepr :: Repr (a -> b) -> a -> b Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr (Either a b) Source #

Methods

fromRepr :: Repr (Either a b) -> Either a b Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr (a, b) Source #

Methods

fromRepr :: Repr (a, b) -> (a, b) Source #

(CoArbitrary a, Function a, Show a, Constructible b) => Constructible (Fun a b) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr (Fun a b) Source #

Methods

fromRepr :: Repr (Fun a b) -> Fun a b Source #

Runners

quickCheck' :: Testable' prop => prop -> IO () Source #

Variant of quickCheck using the alternative Testable'.

quickCheckWith' :: Testable' prop => Args -> prop -> IO () Source #

Variant of quickCheckWith using the alternative Testable'.

Testable properties

class Testable' prop where Source #

Types that represent testable properties.

This is a clone of the Testable class with an improved function instance.

Methods

property' :: prop -> Property Source #

Instances

Instances details
Testable' Bool Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable.Class

Testable' Property Source #

A Property is the canonical type of testable properties.

property' @Property = property @Property = id
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable.Class

Testable' a => Testable' (Gen a) Source #

A generator represents a universally quantified property.

Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable.Class

Methods

property' :: Gen a -> Property Source #

TestEq a => Testable' (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

(Constructible a, Testable' b) => Testable' (a -> b) Source #

A function represents a universally quantified property.

Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable.Class

Methods

property' :: (a -> b) -> Property Source #

(Decidable a, Testable' b) => Testable' (Implication a b) Source #

Just use (==>).

Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Types of testable properties

data Equation a Source #

Equation: an equals sign between two values.

Constructors

(:=:) a a infix 5 

Instances

Instances details
Eq a => Eq (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

(==) :: Equation a -> Equation a -> Bool #

(/=) :: Equation a -> Equation a -> Bool #

Ord a => Ord (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

compare :: Equation a -> Equation a -> Ordering #

(<) :: Equation a -> Equation a -> Bool #

(<=) :: Equation a -> Equation a -> Bool #

(>) :: Equation a -> Equation a -> Bool #

(>=) :: Equation a -> Equation a -> Bool #

max :: Equation a -> Equation a -> Equation a #

min :: Equation a -> Equation a -> Equation a #

Show a => Show (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

showsPrec :: Int -> Equation a -> ShowS #

show :: Equation a -> String #

showList :: [Equation a] -> ShowS #

TestEq a => Testable (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

property :: Equation a -> Property #

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

TestEq a => Testable' (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Eq a => Decidable (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

decide :: Equation a -> Bool Source #

data Implication a b Source #

Expressions denoting a logical implication.

Constructors

(:==>) a b infixr 2 

Instances

Instances details
(Decidable a, Testable b) => Testable (Implication a b) Source #

Just use (==>).

Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

property :: Implication a b -> Property #

propertyForAllShrinkShow :: Gen a0 -> (a0 -> [a0]) -> (a0 -> [String]) -> (a0 -> Implication a b) -> Property #

(Decidable a, Testable' b) => Testable' (Implication a b) Source #

Just use (==>).

Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

type EqImpl a b = Implication (Equation a) (Equation b) Source #

Implication between two equations.

Decidable properties

class Decidable a where Source #

Decidable property.

Methods

decide :: a -> Bool Source #

The definition of decidability: we can compute whether a property is true.

Instances

Instances details
Decidable Bool Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

decide :: Bool -> Bool Source #

Eq a => Decidable (Equation a) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Testable

Methods

decide :: Equation a -> Bool Source #

Testable equality

class TestEq a where Source #

Testable equality

Methods

(=?) :: a -> a -> Property infix 4 Source #

A property that probably fails if the two values are not equal.

(a =? a)  =  property True

Instances

Instances details
TestEq Bool Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Bool -> Bool -> Property Source #

TestEq Char Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Char -> Char -> Property Source #

TestEq Double Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Double -> Double -> Property Source #

TestEq Int Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Int -> Int -> Property Source #

TestEq Integer Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

TestEq Ordering Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

TestEq Word Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Word -> Word -> Property Source #

TestEq () Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: () -> () -> Property Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: [a] -> [a] -> Property Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Maybe a -> Maybe a -> Property Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Identity a -> Identity a -> Property Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Sum a -> Sum a -> Property Source #

(Constructible a, TestEq b) => TestEq (a -> b) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: (a -> b) -> (a -> b) -> Property Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: Either a b -> Either a b -> Property Source #

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

Defined in Test.QuickCheck.HigherOrder.Internal.TestEq

Methods

(=?) :: (a, b) -> (a, b) -> Property Source #

decEq :: (Eq a, Show a) => a -> a -> Property Source #

Default method to convert Eq (decidable equality) into TestEq.

Helpers

ok :: Testable' prop => String -> prop -> (String, Property) Source #

A named property that should pass.

Use ok and ko to construct lists of named properties [(String, Property)], which can be run using quickChecks, or testProperties from tasty-quickcheck.

ko :: Testable' prop => String -> prop -> (String, Property) Source #

A named property that should fail.

See also ok.

quickChecks :: [(String, Property)] -> IO Bool Source #

Execute a list of named properties.

Constructible wrappers

forAll_ :: forall a prop. (Constructible a, Testable' prop) => (a -> prop) -> Property Source #

Equivalent to property' specialized to functions: convert a function to a Property.

data Constructed a Source #

Constructible wrapper with Show and Arbitrary instances that operate on the representation of the argument type.

Deconstruct with the Construct pattern.

This is only useful for property combinators from vanilla QuickCheck, that use the original Testable class instead of Testable' from this library.

pattern Construct :: a -> Constructed a Source #

A unidirectional pattern to deconstruct Constructed values.

CoArbitrary

See also the documentation of Test.Fun.

data a :-> r infixr 1 #

Testable representation of functions (a -> r).

This representation supports random generation, shrinking, and printing, for property testing with QuickCheck or Hedgehog.

Higher-order functions can be represented.

Instances

Instances details
Functor ((:->) a) 
Instance details

Defined in Test.Fun.Internal.Types

Methods

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

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

Foldable ((:->) a) 
Instance details

Defined in Test.Fun.Internal.Types

Methods

fold :: Monoid m => (a :-> m) -> m #

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

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

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

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

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

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

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

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

toList :: (a :-> a0) -> [a0] #

null :: (a :-> a0) -> Bool #

length :: (a :-> a0) -> Int #

elem :: Eq a0 => a0 -> (a :-> a0) -> Bool #

maximum :: Ord a0 => (a :-> a0) -> a0 #

minimum :: Ord a0 => (a :-> a0) -> a0 #

sum :: Num a0 => (a :-> a0) -> a0 #

product :: Num a0 => (a :-> a0) -> a0 #

Traversable ((:->) a) 
Instance details

Defined in Test.Fun.Internal.Types

Methods

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

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

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

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

(CoArbitrary Gen a, Arbitrary r) => Arbitrary (a :-> r) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Function

Methods

arbitrary :: Gen (a :-> r) #

shrink :: (a :-> r) -> [a :-> r] #

applyFun :: (a :-> r) -> a -> r #

Evaluate a representation into the function it represents.

class Applicative gen => CoArbitrary (gen :: Type -> Type) a where #

Implicit, default cogenerator.

Methods

coarbitrary :: Co gen a r #

Instances

Instances details
Applicative gen => CoArbitrary gen Word 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Word r #

Applicative gen => CoArbitrary gen Void 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Void r #

Applicative gen => CoArbitrary gen Ordering 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Ordering r #

Applicative gen => CoArbitrary gen Integer 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Integer r #

Applicative gen => CoArbitrary gen Int 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Int r #

Applicative gen => CoArbitrary gen Bool 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen Bool r #

Applicative gen => CoArbitrary gen () 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen () r #

CoArbitrary gen a => CoArbitrary gen [a] 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen [a] r #

CoArbitrary gen a => CoArbitrary gen (Sum a) 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Sum a) r #

CoArbitrary gen a => CoArbitrary gen (Maybe a) 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Maybe a) r #

CoArbitrary gen a => CoArbitrary gen (Identity a) 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Identity a) r #

(CoArbitrary gen a, CoArbitrary gen b) => CoArbitrary gen (Either a b) 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (Either a b) r #

(CoArbitrary gen a, CoArbitrary gen b) => CoArbitrary gen (a, b) 
Instance details

Defined in Test.Fun.Internal.Generic

Methods

coarbitrary :: Co gen (a, b) r #

(Constructible a, CoArbitrary Gen b) => CoArbitrary Gen (a -> b) Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Function

Methods

coarbitrary :: Co Gen (a -> b) r #

cogenEmbed :: Functor gen => FunName -> (a -> b) -> Co gen b r -> Co gen a r #

Cogenerator for a type a from a cogenerator for b, given an embedding function (a -> b), and a name for that function (used for pretty-printing).

Example

Expand

The common usage is to construct cogenerators for newtypes.

-- Given some cogenerator of Fruit
cogenFruit :: Co Gen Fruit r

-- Wrap Fruit in a newtype
newtype Apple = Apple { unApple :: Fruit }

cogenApple :: Co Gen Apple r
cogenApple = cogenEmbed "unApple" cogenFruit

If cogenFruit generates a function that looks like:

\y -> case y :: Fruit of { ... }

then cogenApple will look like this, where y is replaced with unApple x:

\x -> case unApple x :: Fruit of { ... }

cogenIntegral :: (Applicative gen, Integral a) => TypeName -> Co gen a r #

Cogenerator for an integral type. The name of the type is used for pretty-printing.

Example

Expand
cogenInteger :: Co Gen Integer r
cogenInteger = cogenIntegral "Integer"

cogenInt :: Co Gen Int r
cogenInt = cogenIntegral "Int"

cogenWord :: Co Gen Word r
cogenWord = cogenIntegral "Word"

coarbitraryGeneric :: forall a r gen. (Generic a, GCoArbitrary gen a) => Co gen a r #

Generic implementation of coarbitrary.

-- Assuming MyData is a data type whose fields are all instances of CoArbitrary.

instance CoArbitrary MyData where
  coarbitrary = coarbitraryGeneric