Skip to content

Instantly share code, notes, and snippets.

@bitwombat
Created November 6, 2020 04:17
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save bitwombat/fb47ec6f39c0034f5cdd310b914f12f1 to your computer and use it in GitHub Desktop.
Save bitwombat/fb47ec6f39c0034f5cdd310b914f12f1 to your computer and use it in GitHub Desktop.
Ch16
module InstancesOfFunc where
import Test.QuickCheck
functorIdentity :: (Functor f, Eq (f a)) => f a -> Bool
functorIdentity f = fmap id f == f
functorCompose :: (Eq (f c), Functor f) => (a -> b) -> (b -> c) -> f a -> Bool
functorCompose f g x = (fmap g (fmap f x)) == (fmap (g . f) x)
--1)
newtype Identity a =
Identity a
deriving (Eq, Show)
instance Functor Identity where
fmap f (Identity a) = Identity (f a)
instance Arbitrary a => Arbitrary (Identity a) where
arbitrary = Identity <$> arbitrary
--2)
data Pair a =
Pair a a
deriving (Eq, Show)
instance Functor Pair where
fmap f (Pair a b) = Pair a (f b)
instance Arbitrary a => Arbitrary (Pair a) where
arbitrary = Pair <$> arbitrary
-- Two ways to hint the type to quickcheck
-- let f :: Identity Int -> Bool
-- f x = functorIdentity x
-- or as below
testIdentity :: IO ()
testIdentity = do
let f x = functorIdentity (x :: Identity Int)
quickCheck f
let c = functorCompose (+ 1) (* 2)
let li x = c (x :: Identity Int)
quickCheck li
testPair :: IO ()
testPair = do
let f x = functorIdentity (x :: Pair Int)
quickCheck f
let c = functorCompose (+ 1) (* 2)
let li x = c (x :: Pair Int)
quickCheck li
main :: IO ()
main = do
putStrLn "Identity:"
testIdentity
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment