quickcheck-higherorder-0.1.0.0: QuickCheck extension for higher-order properties

Safe HaskellSafe
LanguageHaskell2010

Test.QuickCheck.HigherOrder.Internal.Constructible

Contents

Synopsis

The Constructible class

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.

Methods

fromRepr :: Repr a -> a Source #

Interpret a representation as a value.

Instances
Constructible Bool Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Bool :: Type Source #

Methods

fromRepr :: Repr Bool -> Bool Source #

Constructible Char Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Char :: Type Source #

Methods

fromRepr :: Repr Char -> Char Source #

Constructible Double Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Double :: Type Source #

Constructible Int Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Int :: Type Source #

Methods

fromRepr :: Repr Int -> Int Source #

Constructible Integer Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Integer :: Type Source #

Constructible Ordering Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Ordering :: Type Source #

Constructible Word Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr Word :: Type Source #

Methods

fromRepr :: Repr Word -> Word Source #

Constructible () Source # 
Instance details

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr () :: Type Source #

Methods

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

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

Defined in Test.QuickCheck.HigherOrder.Internal.Constructible

Associated Types

type Repr [a] :: Type 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) :: Type 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) :: Type 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) :: Type 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) :: Type 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) :: Type 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) :: Type 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) :: Type Source #

Methods

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

The Constructed modifier

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.

Constructors

Constructed (Repr a) a 

pattern Construct :: a -> Constructed a Source #

A unidirectional pattern to deconstruct Constructed values.

mkConstructed :: Constructible a => Repr a -> Constructed a Source #

A smart constructor for constructible values.