Copyright | 2018 Automattic Inc. |
---|---|
License | BSD3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Test.Tasty.QuickCheck.Laws.Monad
Contents
Description
Prebuilt tasty test trees for the Monad
laws. To get started, look at testMonadLaws
.
Synopsis
- testMonadLaws :: (Monad m, Eq a, Eq b, Eq c, Show a, Show t, Show (m a), Arbitrary a, Arbitrary t, Arbitrary (m a), Arbitrary (m b), Arbitrary (m c), CoArbitrary a, CoArbitrary b, Typeable m, Typeable a, Typeable b, Typeable c) => Proxy m -> Proxy t -> Proxy a -> Proxy b -> Proxy c -> (forall u. Eq u => t -> m u -> m u -> Bool) -> TestTree
- testMonadLawRightIdentity :: (Monad m, Eq a, Show t, Show (m a), Arbitrary t, Arbitrary (m a)) => Proxy m -> Proxy t -> Proxy a -> (forall u. Eq u => t -> m u -> m u -> Bool) -> TestTree
- testMonadLawLeftIdentity :: (Monad m, Eq b, Show a, Show t, Arbitrary a, Arbitrary t, Arbitrary (m b), CoArbitrary a) => Proxy m -> Proxy t -> Proxy a -> Proxy b -> (forall u. Eq u => t -> m u -> m u -> Bool) -> TestTree
- testMonadLawAssociativity :: (Monad m, Eq c, Show t, Show (m a), Arbitrary t, Arbitrary (m a), Arbitrary (m b), Arbitrary (m c), CoArbitrary a, CoArbitrary b) => Proxy m -> Proxy t -> Proxy a -> Proxy b -> Proxy c -> (forall u. Eq u => t -> m u -> m u -> Bool) -> TestTree
- testMonadLaws1 :: (Monad m, Checkable a, Show t, Show (m a), Arbitrary t, Arbitrary (m a), Typeable m) => Proxy m -> Proxy t -> Proxy a -> (forall u. Eq u => t -> m u -> m u -> Bool) -> TestTree
- testMonadLaws2 :: (Monad m, Checkable a, Checkable b, Show t, Show (m a), Show (m b), Arbitrary t, Arbitrary (m a), Arbitrary (m b), Typeable m) => Proxy m -> Proxy t -> Proxy a -> Proxy b -> (forall u. Eq u => t -> m u -> m u -> Bool) -> TestTree
- testMonadLaws3 :: (Monad m, Checkable a, Checkable b, Checkable c, Show t, Show (m a), Show (m b), Show (m c), Arbitrary t, Arbitrary (m a), Arbitrary (m b), Arbitrary (m c), Typeable m) => Proxy m -> Proxy t -> Proxy a -> Proxy b -> Proxy c -> (forall u. Eq u => t -> m u -> m u -> Bool) -> TestTree
Documentation
Arguments
:: (Monad m, Eq a, Eq b, Eq c, Show a, Show t, Show (m a), Arbitrary a, Arbitrary t, Arbitrary (m a), Arbitrary (m b), Arbitrary (m c), CoArbitrary a, CoArbitrary b, Typeable m, Typeable a, Typeable b, Typeable c) | |
=> Proxy m | 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 -> m u -> m u -> Bool) | Equality test |
-> TestTree |
Constructs a TestTree
checking that the Monad
class laws hold for m
with value types a
, b
, and c
, using a given equality test for values of type forall u. m u
. The equality context type t
is for constructors m
from which we can only extract a value within a context, such as reader-like constructors.
Monad Laws
testMonadLawRightIdentity Source #
Arguments
:: (Monad m, Eq a, Show t, Show (m a), Arbitrary t, Arbitrary (m a)) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy a | Value type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> TestTree |
x >>= return === x
testMonadLawLeftIdentity Source #
Arguments
:: (Monad m, Eq b, Show a, Show t, Arbitrary a, Arbitrary t, Arbitrary (m b), CoArbitrary a) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy a | Value type |
-> Proxy b | Value type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> TestTree |
return a >>= f === f a
testMonadLawAssociativity Source #
Arguments
:: (Monad m, Eq c, Show t, Show (m a), Arbitrary t, Arbitrary (m a), Arbitrary (m b), Arbitrary (m c), CoArbitrary a, CoArbitrary b) | |
=> Proxy m | 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 -> m u -> m u -> Bool) | Equality test |
-> TestTree |
(x >>= f) >>= g === x >>= (\z -> f z >>= g)
Test Trees
Arguments
:: (Monad m, Checkable a, Show t, Show (m a), Arbitrary t, Arbitrary (m a), Typeable m) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy a | Value type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> TestTree |
All possible value type selections for testMonadLaws
from one choice
Arguments
:: (Monad m, Checkable a, Checkable b, Show t, Show (m a), Show (m b), Arbitrary t, Arbitrary (m a), Arbitrary (m b), Typeable m) | |
=> Proxy m | |
-> Proxy t | |
-> Proxy a | |
-> Proxy b | |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> TestTree |
All possible value type selections for testMonadLaws
from two choices
Arguments
:: (Monad m, Checkable a, Checkable b, Checkable c, Show t, Show (m a), Show (m b), Show (m c), Arbitrary t, Arbitrary (m a), Arbitrary (m b), Arbitrary (m c), Typeable m) | |
=> Proxy m | |
-> Proxy t | |
-> Proxy a | |
-> Proxy b | |
-> Proxy c | |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> TestTree |
All possible value type selections for testMonadLaws
from three choices