[Haskell-beginners] basic Functor, Applicative and Monad instances
Imants Cekusins
imantc at gmail.com
Thu Jul 16 19:52:36 UTC 2015
Here are complete working snippets with Functor, Applicative and Monad
instances. This is my first attempt to write own instances rather than
use ready ones.
Here we go:
module Part.Monad where
import Control.Applicative
{-# ANN module ("HLint: ignore Use let"::String) #-}
{-
Val' { val = b1 } can also be written as
Val' b1
-}
data Val a = Val' {
val::a
} deriving Show
data Weather = Cold | Warm deriving Show
instance Functor Val where
-- (a -> b) -> f a -> f b
fmap ab fa = let a1 = val fa
b1 = ab a1
in Val' { val = b1 }
instance Applicative Val where
-- a -> f a
pure a = Val' { val = a }
-- f (a -> b) -> f a -> f b
(<*>) fab fa = let ab1 = val fab
a1 = val fa
b1 = ab1 a1
in Val' { val = b1 }
instance Monad Val where
-- a -> m a
return a = Val' { val = a }
-- m a -> (a -> m b) -> m b
(>>=) ma amb = let a1 = val ma
in amb a1
-- pure and return in this example are interchangeable
main::Int -> IO()
main i = do -- do: Val as monad
v1 <- pure Val' { val = i } -- pure: applicative
v2 <- return $ over20 <$> v1 -- <$> : functor
print v2
v3 <- return $ Val' weather <*> v2 -- <*> : applicative
print v3
over20::Int-> Bool
over20 i
| i > 20 = True
| otherwise = False
weather::Bool-> Weather
weather False = Cold
weather True = Warm
More information about the Beginners
mailing list