Request to review my attempt at understanding Monads

Hi, I've been reading the papers titled "Comprehending Monads" and "Monadic Parser Combinator" to understand Monads and I think I am beginning to understand it. In my attempt to validate my understanding, I've written my version of List data structure with Monadic behaviour - I'd appreciate answers to the following queries - 1. Comments about the functions I've written 2. I've used the do notation at the bottom which is a result of my List being a Monad - are there any other benefits that comes in because of List being a Monad? What would MonadPlus provide me? 3. The comprehension syntax for Lists in Haskell - can that be used in anyway for other Monads? Regards, Kashyap import Monad ( MonadPlus(..) ) data List a = Cons a (List a) | Empty deriving Show --myMap :: (t -> a) -> List t -> List a myMap :: (t -> a) -> List t -> List a myMap f Empty = Empty myMap f (Cons a rest) = Cons (f a) (myMap f rest) --myAppend :: List a -> List a -> List a myAppend :: List a -> List a -> List a myAppend Empty l = l myAppend l Empty = l myAppend (Cons a rest) l = Cons a (myAppend rest l) --myConcat :: List (List a) -> List a myConcat :: List (List a) -> List a myConcat Empty= Empty myConcat (Cons Empty rest)= myConcat rest myConcat (Cons list rest)= myAppend list (myConcat rest) instance Monad List where return a = Cons a Empty Empty >>= f = Empty l >>= f = myConcat (myMap f l) instance MonadPlus List where p `mplus` q = myAppend p q mzero= Empty list2myList :: [a] -> List a list2myList [] = Empty list2myList (x:xs) = Cons x (list2myList xs) l1 = list2myList [1..10] l2 = do x <- l1 y <- Cons (2*x) Empty return y

2009/12/28 CK Kashyap
1. Comments about the functions I've written
Maybe your indentation was eaten by your mailer; but please indent the operations within a `do' block and the definitions under a `where'. You should make a `Functor' instance since monads are all functors (though the typeclass does not enforce this).
2. I've used the do notation at the bottom which is a result of my List being a Monad - are there any other benefits that comes in because of List being a Monad? What would MonadPlus provide me?
You can use `guard' and `when' and other monadic operations. The `MonadPlus' instance gives you access to `msum'. It's not just about `do' notation :)
3. The comprehension syntax for Lists in Haskell - can that be used in anyway for other Monads?
Not anymore, though Gofer used to allow "monad comprehensions". -- Jason Dusek

Thanks Jason,
You should make a `Functor' instance since monads are all functors (though the typeclass does not enforce this).
What are the benefits of making it an instance of Functor?
You can use `guard' and `when' and other monadic operations. The `MonadPlus' instance gives you access to `msum'. It's not just about `do' notation :)
I'd appreciate it very much if you could give me some pointers on the usages of guard, when and msum. Regards, Kashyap

On Tue, 2009-12-29 at 02:07 -0800, CK Kashyap wrote:
Thanks Jason,
You should make a `Functor' instance since monads are all functors (though the typeclass does not enforce this).
What are the benefits of making it an instance of Functor?
1. For example to use function of type Functor f => f a -> f d. 2. Also you need Functor to have Applicative which is rather useful (f < $> arg1 <*> arg2 <*> arg3 <*> ... as opposed to return f `ap` arg1 `ap` arg2 `ap` arg3 ..., (*>), (<*) etc.) 3. Because it is functor ;). Every Monad is functor: instance Functor MyMonad where fmap = liftM instance Applicative MyMonad where pure = return (<*>) = ap 4. If you use Control.Applicative you can find: read <$> getLine I find it much more readable then liftM read getLine (it looks nearly like read $ getLine). Regards

imo, the most import ingredient to understand monads, is to understand
lazy evaluation. In Haskell, everything is about values. If you have a
function f :: a -> b, then f x stands for a value of type b (nothing
is evaluated yet).
Now, if you have another function g :: a -> M b, then g x stands for a
value of type M b, that is, a value of type b requiring something more
(encoded by the monad M). Depending on which Monad you used, you need
to do something the the value M b to get to the actual value b. In the
case of the State monad, you have to run it with an initial state. In
the case of IO, you can't do anything and so you have to give the
value to the runtime-system (via the main-function). In the case of
the List monad (which represents non-determinism), you can choose any
element of the resulting list, or, more commonly, use every possible
result (i.e. the whole list).
--
Thomas Danecker
2009/12/29 Maciej Piechotka
On Tue, 2009-12-29 at 02:07 -0800, CK Kashyap wrote:
Thanks Jason,
You should make a `Functor' instance since monads are all functors (though the typeclass does not enforce this).
What are the benefits of making it an instance of Functor?
1. For example to use function of type Functor f => f a -> f d.
2. Also you need Functor to have Applicative which is rather useful (f < $> arg1 <*> arg2 <*> arg3 <*> ... as opposed to return f `ap` arg1 `ap` arg2 `ap` arg3 ..., (*>), (<*) etc.)
3. Because it is functor ;). Every Monad is functor:
instance Functor MyMonad where fmap = liftM instance Applicative MyMonad where pure = return (<*>) = ap
4. If you use Control.Applicative you can find: read <$> getLine I find it much more readable then liftM read getLine (it looks nearly like read $ getLine).
Regards
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

imo, the most import ingredient to understand monads, is to understand lazy evaluation. In Haskell, everything is about values. If you have a function f :: a -> b, then f x stands for a value of type b (nothing is evaluated yet). Now, if you have another function g :: a -> M b, then g x stands for a value of type M b, that is, a value of type b requiring something more (encoded by the monad M). Depending on which Monad you used, you need to do something the the value M b to get to the actual value b. In the case of the State monad, you have to run it with an initial state. In the case of IO, you can't do anything and so you have to give the value to the runtime-system (via the main-function). In the case of the List monad (which represents non-determinism), you can choose any element of the resulting list, or, more commonly, use every possible result (i.e. the whole list).
One thing is missing here: The interesting aspect of a monad is, that it always allows you to "compose". Via the bind function (>>=) :: m b -> (b -> m c) -> m c, you can take a value of M b and derive from it a new value of M c by using the previously encapsulated value b. -- Thomas Danecker

CK Kashyap
What are the benefits of making it an instance of Functor?
The ability to use fmap rather than liftM.
I'd appreciate it very much if you could give me some pointers on the usages of guard, when and msum.
You can use when to have an operation occur only when a condition is true: when :: (Monad m) => Bool -> m () -> m () e.g. to delete a file only if it actually exists: ,---- | tryDeleteFile :: FilePath -> IO () | tryDeleteFile f = do ex <- doesFileExist f | when ex (removeFile f) `---- -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

I happen to think that the only good way to approach monads is mathematically. Uses come out naturally, once you understand what it is that a monad "does". I'll make a short speech and then comment on your questions. First, an example. I will assume that there are some things you will only do outdoors. And there are some things you will only do in your home. If you are in your home, and decide you need to do one of these "outdoor" things, you need to do something VERY SPECIFIC first. You need to go outdoors. Second, a monad is conceptually a "one argument" function/functor. Outside of the Haskell/programming context, "Monadic" means "one argument". This is important, because a function with one argument bears a special relationship to its argument. Using current mathematical convention, the function "goes" on the left. And the argument "goes" on the right. Obviously, leftness and rightness are duals, so it doesn't particularly matter which goes where, as long as one is consistent. Continuing that point, the functions "bind" and "return" capture the notion of "moving right" and "moving left". This is literally captures the notion of a "side effect". The effect of moving the context of computation left or right. A simple example is:
data Left a = LeftA a | LeftB a data Right = Right
-- Note that the type (Left Right) is a product of types. -- (Left Right) contains the values (LeftA Right) and (LeftB Right).
-- Compare that to LeftRight in: -- data Left = LeftA | LeftB -- data Right = Right -- type LeftRight = (Left, Right) -- contains the values (LeftA, Right) and (LeftB, Right).
instance Monad Left where return a = LeftA a -- moves "execution context" to the left, in virtue -- of the fact that any function on (Left a) has to work -- on every type a. (LeftA a) >>= f = f a (LeftB a) >>= f = f a
The only complication is that bind (>>=) expects to bind variables to functions that return a monadic type. So, basically, a call to bind unwraps the monadic type, applies a function, and then "automatically" moves the scope back left, as if you hit the end of a typewriter's line. This is only for convenience. You could (and sometimes have to) use return in order to "return to the left". Monads are pretty deep mathematically. Every Monad defines a "join" and "eval" function in terms of bind and return, and the Monad type class does this for you. You can use "join" to construct queries against a monad, and eval to "run" a monad, like a state machine. (Conceptually, the Haskell runtime calls the IO monad's "specially defined" eval method on "Main.main". This is the only Haskell monad whose eval function is not defined in terms of >>= and return, as far as I know.) On to your questions:
are there any other benefits that comes in because of List being a Monad? What would MonadPlus provide me?
If you think List is the right monad to work in, you might as well stick to List functions and ignore do-notation. If you think you might need a more general monad, you may as well use do-notation. Lists have more structure than "all monads", so we can define more functions on lists than we can on an arbitrary monad. "MonadPlus" applies to Monads that have a sort of "additive" structure. There's no "sensible" way to add (LeftA a) and (LeftB a) values together, but we can impose one by declaring Left as a MonadPlus. If you allow some abuse of the syntax, this might be a better example:
-- we are treating the Integers as one argument data constructors -- this code will not run, because we are abusing the Integers. -- This is kind of like an "infinite" Maybe monad type Count a = 0 | 1 a | 2 a | 3 a | 4 a | 5 a | ... instance Monad Count where return a = 0 a (int, a) >>= f = f a
instance MonadPlus Count where mzero = 0 m `mplus` n = (m + n) -- still abusing notation. m and n are "really" (m a) and (n b) -- but this is clear enough, and captures the semantics of counting
The MonadPlus instance lets us add "Count" values, without regard to what is being counted. Note that while Count's addition function is commutative (so that m `mplus` n = n `mplus` n), that does not have to be true in general. Lists are a good example. Adding to a list amounts to concatenating values to it.
3. The comprehension syntax for Lists in Haskell - can that be used in anyway for other Monads?
Partly. The <- in your l2 function is really the most important part of comprehension syntax. return does the wrapping you might expect from something like "M (x <- blarg)" There isn't "M ( x <- blarg )" type syntax for arbitrary monads. Lists are a special case, since [] is a special case as a type constructor.

2009/12/29 Alexander Solla
Every Monad defines a "join" and "eval" function in terms of bind and return, and the Monad type class does this for you. You can use "join" to construct queries against a monad, and eval to "run" a monad, like a state machine. (Conceptually, the Haskell runtime calls the IO monad's "specially defined" eval method on "Main.main". This is the only Haskell monad whose eval function is not defined in terms of >>= and return, as far as I know.)
Maybe I am misunderstanding you, but `eval :: M t -> t' does not fall out of the definition of a monad. You need more than monadicity -- you need an algebra for `M' at `t'. -- Jason Dusek

On Tue, Dec 29, 2009 at 7:58 AM, CK Kashyap
I'd appreciate answers to the following queries - 1. Comments about the functions I've written
{-# LANGUAGE UnicodeSyntax #-} import Monad ( MonadPlus(..) ) data List α = Cons α (List α) | Empty deriving Show If you look at your definitions of 'myMap', 'myAppend' and 'myConcat' you will notice that they all follow a similar pattern which can be abstracted in a so called "catamorphism" (or in normal Haskell a "fold"): myFoldr ∷ (α → β → β) → β → List α → β myFoldr f z = myFoldr_f_z where myFoldr_f_z Empty = z myFoldr_f_z (Cons x xs) = f x $ myFoldr_f_z xs myMap ∷ (α → β) → List α → List β myMap f = myFoldr (Cons . f) Empty myAppend ∷ List α → List α → List α myAppend xs ys = myFoldr Cons ys xs myConcat ∷ List (List α) → List α myConcat = myFoldr myAppend Empty instance Monad List where return a = Cons a Empty l >>= f = myConcat $ myMap f l instance MonadPlus List where mplus = myAppend mzero = Empty list2myList ∷ [α] → List α list2myList = foldr Cons Empty regards, Bas
participants (7)
-
Alexander Solla
-
Bas van Dijk
-
CK Kashyap
-
Ivan Lazar Miljenovic
-
Jason Dusek
-
Maciej Piechotka
-
Thomas Danecker