| 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.ErrorMonad
Contents
Description
Synopsis
- testErrorMonadLaws :: (Monad m, Eq a, Eq b, Show t, Show e, Show a, Arbitrary t, Arbitrary e, Arbitrary a, Arbitrary (m a), Arbitrary (m b), CoArbitrary e, CoArbitrary a, Typeable m, Typeable e, Typeable a, Typeable b) => Proxy m -> Proxy t -> Proxy e -> Proxy a -> Proxy b -> (forall u. Eq u => t -> m u -> m u -> Bool) -> (forall u. e -> m u) -> (m a -> (e -> m a) -> m a) -> TestTree
- testErrorMonadLawCatchReturn :: (Monad m, Eq a, Show t, Show a, Arbitrary t, Arbitrary a, Arbitrary (m a), CoArbitrary e) => Proxy m -> Proxy t -> Proxy e -> Proxy a -> (forall u. Eq u => t -> m u -> m u -> Bool) -> (m a -> (e -> m a) -> m a) -> TestTree
- testErrorMonadLawCatchThrow :: (Monad m, Eq a, Show t, Show e, Arbitrary t, Arbitrary e, Arbitrary (m a), CoArbitrary e) => Proxy m -> Proxy t -> Proxy e -> Proxy a -> (forall u. Eq u => t -> m u -> m u -> Bool) -> (forall u. e -> m u) -> (m a -> (e -> m a) -> m a) -> TestTree
- testErrorMonadLawCatchThrowThrow :: (Monad m, Eq a, Show t, Show e, Arbitrary t, Arbitrary e) => Proxy m -> Proxy t -> Proxy e -> Proxy a -> (forall u. Eq u => t -> m u -> m u -> Bool) -> (forall u. e -> m u) -> (m a -> (e -> m a) -> m a) -> TestTree
- testErrorMonadLawThrowBind :: (Monad m, Eq b, Show t, Show e, Arbitrary t, Arbitrary e, Arbitrary (m b), CoArbitrary a) => Proxy m -> Proxy t -> Proxy e -> Proxy a -> Proxy b -> (forall u. Eq u => t -> m u -> m u -> Bool) -> (forall u. e -> m u) -> TestTree
Documentation
Arguments
| :: (Monad m, Eq a, Eq b, Show t, Show e, Show a, Arbitrary t, Arbitrary e, Arbitrary a, Arbitrary (m a), Arbitrary (m b), CoArbitrary e, CoArbitrary a, Typeable m, Typeable e, Typeable a, Typeable b) | |
| => Proxy m | Type constructor under test | 
| -> Proxy t | Equality context for  | 
| -> Proxy e | Error type | 
| -> Proxy a | Value type | 
| -> Proxy b | Value type | 
| -> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test | 
| -> (forall u. e -> m u) | throw | 
| -> (m a -> (e -> m a) -> m a) | catch | 
| -> TestTree | 
Constructs a TestTree checking that the error monad laws hold for m with error type e and value types a and b, 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.
Error Monad Laws
testErrorMonadLawCatchReturn Source #
Arguments
| :: (Monad m, Eq a, Show t, Show a, Arbitrary t, Arbitrary a, Arbitrary (m a), CoArbitrary e) | |
| => Proxy m | Type constructor under test | 
| -> Proxy t | Equality context for  | 
| -> Proxy e | Error type | 
| -> Proxy a | Value type | 
| -> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test | 
| -> (m a -> (e -> m a) -> m a) | catch | 
| -> TestTree | 
catch (return a) h === return a
testErrorMonadLawCatchThrow Source #
Arguments
| :: (Monad m, Eq a, Show t, Show e, Arbitrary t, Arbitrary e, Arbitrary (m a), CoArbitrary e) | |
| => Proxy m | Type constructor under test | 
| -> Proxy t | Equality context for  | 
| -> Proxy e | Error type | 
| -> Proxy a | Value type | 
| -> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test | 
| -> (forall u. e -> m u) | throw | 
| -> (m a -> (e -> m a) -> m a) | catch | 
| -> TestTree | 
catch (throw e) h === h e
testErrorMonadLawCatchThrowThrow Source #
Arguments
| :: (Monad m, Eq a, Show t, Show e, Arbitrary t, Arbitrary e) | |
| => Proxy m | Type constructor under test | 
| -> Proxy t | Equality context for  | 
| -> Proxy e | Error type | 
| -> Proxy a | Value type | 
| -> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test | 
| -> (forall u. e -> m u) | throw | 
| -> (m a -> (e -> m a) -> m a) | catch | 
| -> TestTree | 
catch (throw e) throw === throw e
testErrorMonadLawThrowBind Source #
Arguments
| :: (Monad m, Eq b, Show t, Show e, Arbitrary t, Arbitrary e, Arbitrary (m b), CoArbitrary a) | |
| => Proxy m | Type constructor under test | 
| -> Proxy t | Equality context for  | 
| -> Proxy e | Error type | 
| -> Proxy a | Value type | 
| -> Proxy b | Value type | 
| -> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test | 
| -> (forall u. e -> m u) | throw | 
| -> TestTree | 
throw e >>= f === throw e