summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorKjetil Orbekk <kjetil.orbekk@gmail.com>2016-03-11 03:43:39 +0100
committerKjetil Orbekk <kjetil.orbekk@gmail.com>2016-03-11 03:47:27 +0100
commit475872efcb9bc8496cedcbf4f978fab44402c046 (patch)
treef67d85c8c3708933733ddef453647ef68b56f291
parentf077bc7aa0f41a10b595307124e2051c2fbdfbf0 (diff)
Add quickcheck example with functions.
-rw-r--r--qcheck.hs30
1 files changed, 30 insertions, 0 deletions
diff --git a/qcheck.hs b/qcheck.hs
new file mode 100644
index 0000000..382179b
--- /dev/null
+++ b/qcheck.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+import Test.QuickCheck
+import Test.QuickCheck.Function
+
+newtype ReversingList a = ReversingList [a]
+ deriving (Show, Eq, Arbitrary)
+
+-- This ReversingList is a Functor instance that reverses the elements while it
+-- maps over them.
+instance Functor ReversingList where
+ fmap f (ReversingList xs) = ReversingList (reverse (fmap f xs))
+
+-- The functor law is that (fmap f . fmap g) == fmap (f . g).
+prop_functorLaw (Fun _ f) (Fun _ g) xs =
+ (fmap f . fmap g) xs == fmap (f . g) xs
+
+ where types = ( xs :: ReversingList Int
+ , f :: Int -> Int
+ , g :: Int -> Int )
+
+main = quickCheck prop_functorLaw
+
+{- Output:
+
+*** Failed! Falsifiable (after 6 tests and 19 shrinks):
+{-5->1, _->0}
+{0->-5, _->0}
+ReversingList [1,0]
+
+-}