basic Functor, Applicative and Monad instances

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

This would all be much easier with pattern matching. For example: instance Functor Val where fmap f (Val x) = Val (f x) instance Applicative Val where pure = Val Val f <*> Val x = Val (f x)

Cheers, Rein. This is new for me. I tried to make it work. BTW the monad instance is not used. Commenting it out has no effect on running main. How can I apply Val (not IO) Monad instance in this example? Could you suggest a simple change?

v2: Val monad is now necessary: main::Int -> Val Weather main i = do -- do: Val as monad v1 <- return $ Val' i -- pure: applicative v2 <- return $ over20 <$> v1 -- <$> : functor v3 <- Val' weather <*> v2 -- <*> : applicative return v3

based on this snippet and Rein's comment, here is monad file template for intellij Idea to make new monads a quick exercise: module ${PACKAGE_NAME}.${NAME} where data ${Type} a = ${ctor} { ${prop}::a } instance Functor ${Type} where -- (a -> b) -> f a -> f b -- fmap f (${ctor} x) = ${ctor} (f x) fmap ab fa = let a1 = ${prop} fa b1 = ab a1 in fa { ${prop} = b1 } instance Applicative ${Type} where -- a -> f a -- pure = ${ctor} pure a = ${ctor} { ${prop} = a } -- f (a -> b) -> f a -> f b -- ${ctor} f <*> ${ctor} x = ${ctor} (f x) (<*>) fab fa = let ab1 = ${prop} fab a1 = ${prop} fa b1 = ab1 a1 in fa { ${prop} = b1 } instance Monad ${Type} where -- a -> m a return a = ${ctor} { ${prop} = a } -- m a -> (a -> m b) -> m b (>>=) ma amb = let a1 = ${prop} ma in amb a1

You have the types of the functions commented out in the instances. If you use {-# LANGUAGE InstanceSigs #-} you can write them for real (and be sure that they're accurate)
Tom
El Jul 17, 2015, a las 3:53, Imants Cekusins
based on this snippet and Rein's comment, here is monad file template for intellij Idea to make new monads a quick exercise:
module ${PACKAGE_NAME}.${NAME} where
data ${Type} a = ${ctor} { ${prop}::a }
instance Functor ${Type} where -- (a -> b) -> f a -> f b -- fmap f (${ctor} x) = ${ctor} (f x) fmap ab fa = let a1 = ${prop} fa b1 = ab a1 in fa { ${prop} = b1 }
instance Applicative ${Type} where -- a -> f a -- pure = ${ctor} pure a = ${ctor} { ${prop} = a }
-- f (a -> b) -> f a -> f b -- ${ctor} f <*> ${ctor} x = ${ctor} (f x) (<*>) fab fa = let ab1 = ${prop} fab a1 = ${prop} fa b1 = ab1 a1 in fa { ${prop} = b1 }
instance Monad ${Type} where -- a -> m a return a = ${ctor} { ${prop} = a }
-- m a -> (a -> m b) -> m b (>>=) ma amb = let a1 = ${prop} ma in amb a1 _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (3)
-
amindfv@gmail.com
-
Imants Cekusins
-
Rein Henrichs