[commit: packages/containers] changelog-foldtree, cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-184-generic, revert-408-bugfix_394: Add tests for Applicative and Monad instances (0decaa1)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:37:00 UTC 2017


Repository : ssh://git@git.haskell.org/containers

On branches: changelog-foldtree,cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-184-generic,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/0decaa120039ff4bafbfd4cc62306925a2c31475

>---------------------------------------------------------------

commit 0decaa120039ff4bafbfd4cc62306925a2c31475
Author: David Feuer <David.Feuer at gmail.com>
Date:   Thu Dec 18 12:44:57 2014 -0500

    Add tests for Applicative and Monad instances
    
    Unfortunately, these tests are rather slow, so I hid them behind
    a SLOW_TESTS macro. I don't know nearly enough about cabal to know
    how to arrange for tests to be run conditionally, so hopefully
    someone else can set that up properly.


>---------------------------------------------------------------

0decaa120039ff4bafbfd4cc62306925a2c31475
 tests/seq-properties.hs | 28 ++++++++++++++++++++++++++++
 1 file changed, 28 insertions(+)

diff --git a/tests/seq-properties.hs b/tests/seq-properties.hs
index def17b3..2b4774d 100644
--- a/tests/seq-properties.hs
+++ b/tests/seq-properties.hs
@@ -17,6 +17,9 @@ import qualified Prelude
 import qualified Data.List
 import Test.QuickCheck hiding ((><))
 import Test.QuickCheck.Poly
+#ifdef SLOW_TESTS
+import Test.QuickCheck.Function
+#endif
 import Test.Framework
 import Test.Framework.Providers.QuickCheck2
 
@@ -93,6 +96,11 @@ main = defaultMain
        , testProperty "zipWith3" prop_zipWith3
        , testProperty "zip4" prop_zip4
        , testProperty "zipWith4" prop_zipWith4
+#ifdef SLOW_TESTS
+       , testProperty "<*>" prop_ap
+       , testProperty "*>" prop_then
+       , testProperty ">>=" prop_bind
+#endif
        ]
 
 ------------------------------------------------------------------------
@@ -588,6 +596,26 @@ prop_zipWith4 xs ys zs ts =
     toList' (zipWith4 f xs ys zs ts) ~= Data.List.zipWith4 f (toList xs) (toList ys) (toList zs) (toList ts)
   where f = (,,,)
 
+-- Applicative operations
+
+#ifdef SLOW_TESTS
+prop_ap :: Seq A -> Seq B -> Bool
+prop_ap xs ys =
+    toList' ((,) <$> xs <*> ys) ~= ( (,) <$> toList xs <*> toList ys )
+
+prop_then :: Seq A -> Seq B -> Bool
+prop_then xs ys =
+    toList' (xs *> ys) ~= (toList xs *> toList ys)
+#endif
+
+-- Monad operations
+
+#ifdef SLOW_TESTS
+prop_bind :: Seq A -> Fun A (Seq B) -> Bool
+prop_bind xs (Fun _ f) =
+    toList' (xs >>= f) ~= (toList xs >>= toList . f)
+#endif
+
 -- Simple test monad
 
 data M a = Action Int a



More information about the ghc-commits mailing list