Copyright | 2018 Automattic Inc. |
---|---|
License | BSD3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
State axioms taken from Gibbons and Hinze, Just do it: simple monadic reasoning, at http://www.cs.ox.ac.uk/jeremy.gibbons/publications/mr.pdf.
Synopsis
- testStateMonadLaws :: (Monad m, Eq s, Eq a, Show t, Show s, Arbitrary t, Arbitrary s, Arbitrary (m a), CoArbitrary s, Typeable m, Typeable s, Typeable a) => Proxy m -> Proxy t -> Proxy s -> Proxy a -> (forall u. Eq u => t -> m u -> m u -> Bool) -> m s -> (s -> m ()) -> TestTree
- testStateMonadLawPutPut :: (Monad m, Show t, Show s, Arbitrary t, Arbitrary s) => Proxy m -> Proxy t -> Proxy s -> (forall u. Eq u => t -> m u -> m u -> Bool) -> (s -> m ()) -> TestTree
- testStateMonadLawPutGet :: (Monad m, Eq s, Show t, Show s, Arbitrary t, Arbitrary s) => Proxy m -> Proxy t -> Proxy s -> (forall u. Eq u => t -> m u -> m u -> Bool) -> m s -> (s -> m ()) -> TestTree
- testStateMonadLawGetPut :: (Monad m, Show t, Arbitrary t) => Proxy m -> Proxy t -> Proxy s -> (forall u. Eq u => t -> m u -> m u -> Bool) -> m s -> (s -> m ()) -> TestTree
- testStateMonadLawGetGet :: (Monad m, Eq a, Show t, Arbitrary t, Arbitrary (m a), CoArbitrary s) => Proxy m -> Proxy t -> Proxy s -> Proxy a -> (forall u. Eq u => t -> m u -> m u -> Bool) -> m s -> TestTree
Documentation
:: (Monad m, Eq s, Eq a, Show t, Show s, Arbitrary t, Arbitrary s, Arbitrary (m a), CoArbitrary s, Typeable m, Typeable s, Typeable a) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy s | State type |
-> Proxy a | Value type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> m s | get |
-> (s -> m ()) | put |
-> TestTree |
Constructs a TestTree
checking that the state monad laws hold for m
with state type s
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.
State Monad Laws
testStateMonadLawPutPut Source #
:: (Monad m, Show t, Show s, Arbitrary t, Arbitrary s) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy s | State type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> (s -> m ()) | put |
-> TestTree |
put s1 >> put s2 === put s2
testStateMonadLawPutGet Source #
:: (Monad m, Eq s, Show t, Show s, Arbitrary t, Arbitrary s) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy s | State type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> m s | get |
-> (s -> m ()) | put |
-> TestTree |
put s >> get === put s >> return s
testStateMonadLawGetPut Source #
:: (Monad m, Show t, Arbitrary t) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy s | State type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> m s | get |
-> (s -> m ()) | put |
-> TestTree |
get >>= put === return ()
testStateMonadLawGetGet Source #
:: (Monad m, Eq a, Show t, Arbitrary t, Arbitrary (m a), CoArbitrary s) | |
=> Proxy m | Type constructor under test |
-> Proxy t | Equality context for |
-> Proxy s | State type |
-> Proxy a | Value type |
-> (forall u. Eq u => t -> m u -> m u -> Bool) | Equality test |
-> m s | get |
-> TestTree |
get >>= \s -> get >>= k s === get >>= \s -> k s s