Copyright | 2018 Automattic Inc. |
---|---|
License | BSD3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- testFunctorLaws :: (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 -> Proxy t -> Proxy a -> Proxy b -> Proxy c -> (forall u. Eq u => t -> f u -> f u -> Bool) -> TestTree
- testFunctorLawIdentity :: (Functor f, Eq a, Show t, Show (f a), Arbitrary t, Arbitrary (f a)) => Proxy f -> Proxy t -> Proxy a -> (forall u. Eq u => t -> f u -> f u -> Bool) -> TestTree
- testFunctorLawComposite :: (Functor f, Eq c, Show t, Show (f a), Arbitrary t, Arbitrary b, Arbitrary c, Arbitrary (f a), CoArbitrary a, CoArbitrary b) => Proxy f -> Proxy t -> Proxy a -> Proxy b -> Proxy c -> (forall u. Eq u => t -> f u -> f u -> Bool) -> TestTree
- testFunctorLaws1 :: (Functor f, Checkable a, Show t, Show (f a), Arbitrary t, Arbitrary (f a), Typeable f) => Proxy f -> Proxy t -> Proxy a -> (forall u. Eq u => t -> f u -> f u -> Bool) -> TestTree
- testFunctorLaws2 :: (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 -> Proxy t -> Proxy a -> Proxy b -> (forall u. Eq u => t -> f u -> f u -> Bool) -> TestTree
- testFunctorLaws3 :: (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 -> Proxy t -> Proxy a -> Proxy b -> Proxy c -> (forall u. Eq u => t -> f u -> f u -> Bool) -> TestTree
Documentation
:: (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 |
-> 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 #
:: (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 |
-> Proxy a | Value type |
-> (forall u. Eq u => t -> f u -> f u -> Bool) | Equality test |
-> TestTree |
fmap id x === x
testFunctorLawComposite Source #
:: (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 |
-> 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
:: (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 |
-> 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
:: (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 |
-> 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
:: (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 |
-> 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