tasty-quickcheck-laws-0.0.3: Pre-built tasty trees for checking lawful class properties using QuickCheck

Copyright2018 Automattic Inc.
LicenseBSD3
MaintainerNathan Bloomfield (nbloomf@gmail.com)
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Test.Tasty.QuickCheck.Laws.Functor

Contents

Description

 
Synopsis

Documentation

testFunctorLaws Source #

Arguments

:: (Functor f, Eq a, Eq c, Show t, Show (f a), Arbitrary t, Arbitrary b, Arbitrary c, Arbitrary (f a), CoArbitrary a, CoArbitrary b, Typeable f, Typeable a, Typeable b, Typeable c) 
=> Proxy f

Type constructor under test

-> Proxy t

Equality context for f

-> Proxy a

Value type

-> Proxy b

Value type

-> Proxy c

Value type

-> (forall u. Eq u => t -> f u -> f u -> Bool)

Equality test

-> TestTree 

Constructs a TestTree checking that the functor laws hold for f with value types a, b, and c, using a given equality test for values of type forall u. f u. The equality context type t is for constructors f from which we can only extract a value within a context, such as reader-like constructors.

Functor Laws

testFunctorLawIdentity Source #

Arguments

:: (Functor f, Eq a, Show t, Show (f a), Arbitrary t, Arbitrary (f a)) 
=> Proxy f

Type constructor under test

-> Proxy t

Equality context for f

-> Proxy a

Value type

-> (forall u. Eq u => t -> f u -> f u -> Bool)

Equality test

-> TestTree 
fmap id x === x

testFunctorLawComposite Source #

Arguments

:: (Functor f, Eq c, Show t, Show (f a), Arbitrary t, Arbitrary b, Arbitrary c, Arbitrary (f a), CoArbitrary a, CoArbitrary b) 
=> Proxy f

Type constructor under test

-> Proxy t

Equality context for f

-> Proxy a

Value type

-> Proxy b

Value type

-> Proxy c

Value type

-> (forall u. Eq u => t -> f u -> f u -> Bool)

Equality test

-> TestTree 
fmap (f . g) x === (fmap f . fmap g) x

Test Trees

testFunctorLaws1 Source #

Arguments

:: (Functor f, Checkable a, Show t, Show (f a), Arbitrary t, Arbitrary (f a), Typeable f) 
=> Proxy f

Type constructor under test

-> Proxy t

Equality context for f

-> Proxy a

Value type

-> (forall u. Eq u => t -> f u -> f u -> Bool)

Equality test

-> TestTree 

All possible value type selections for testFunctorLaws from one choice

testFunctorLaws2 Source #

Arguments

:: (Functor f, Checkable a, Checkable b, Show t, Show (f a), Show (f b), Arbitrary t, Arbitrary (f a), Arbitrary (f b), Typeable f) 
=> Proxy f

Type constructor under test

-> Proxy t

Equality context for f

-> Proxy a

Value type

-> Proxy b

Value type

-> (forall u. Eq u => t -> f u -> f u -> Bool)

Equality test

-> TestTree 

All possible value type selections for testFunctorLaws from two choices

testFunctorLaws3 Source #

Arguments

:: (Functor f, Checkable a, Checkable b, Checkable c, Show t, Show (f a), Show (f b), Show (f c), Arbitrary t, Arbitrary (f a), Arbitrary (f b), Arbitrary (f c), Typeable f) 
=> Proxy f

Type constructor under test

-> Proxy t

Equality context for f

-> Proxy a

Value type

-> Proxy b

Value type

-> Proxy c

Value type

-> (forall u. Eq u => t -> f u -> f u -> Bool)

Equality test

-> TestTree 

All possible value type selections for testFunctorLaws from three choices