What is MonadPlus good for?

I have seen lots of examples that show how it's useful to make some type constructor into an instance of Monad. Where can I find examples showing why it's good to take the trouble to show that something is also a MonadPlus? (I know there are many examples of things that *are* MonadPluses; what I want to know is why this is interesting. :-) Thanks, - Benjamin

On Sat, Feb 12, 2005 at 01:08:59PM -0500, Benjamin Pierce wrote:
I have seen lots of examples that show how it's useful to make some type constructor into an instance of Monad.
Where can I find examples showing why it's good to take the trouble to show that something is also a MonadPlus? (I know there are many examples of things that *are* MonadPluses; what I want to know is why this is interesting. :-)
Thanks,
- Benjamin
As a start, free access to countless general functions as soon as you define a MonadPlus instance for your datatype. (Errr, `guard' and `msum', as long as one stays within the Haskell98 standard libraries ;) Groeten, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

As a start, free access to countless general functions as soon as you define a MonadPlus instance for your datatype. (Errr, `guard' and `msum', as long as one stays within the Haskell98 standard libraries ;)
Yes, those are good examples. (But I'd still be interested to see some of the countless others... :-) Thanks, - Benjamin

On Sat, Feb 12, 2005 at 01:47:06PM -0500, Benjamin Pierce wrote:
As a start, free access to countless general functions as soon as you define a MonadPlus instance for your datatype. (Errr, `guard' and `msum', as long as one stays within the Haskell98 standard libraries ;)
Yes, those are good examples. (But I'd still be interested to see some of the countless others... :-)
Thanks,
- Benjamin
Network.URI and Data.Generics also define a few functions which require MonadPlus instances. Can't find anything else right now. Nor do I know of the (countless? ;)) more theoretical reasons to define instances. -- Nobody can be exactly like me. Even I have trouble doing it.

On Sat, Feb 12, 2005 at 01:08:59PM -0500, Benjamin Pierce wrote:
I have seen lots of examples that show how it's useful to make some type constructor into an instance of Monad.
Where can I find examples showing why it's good to take the trouble to show that something is also a MonadPlus? (I know there are many examples of things that *are* MonadPluses; what I want to know is why this is interesting. :-)
I've been working on a typeclass that derives from MonadPlus which will encapsulate certain kinds of IO. With MonadPlus, you can write monadic code with exceptions and everything that may not be executed in the IO monad. You just use fail to throw exceptions, and mplus to catch them. class MonadPlus m => ReadableDirectory m where mInCurrentDirectory :: FilePath -> m a -> m a mGetDirectoryContents :: m [FilePath] mReadFilePS :: FilePath -> m PackedString mReadFilePSs :: FilePath -> m [PackedString] mReadFilePSs f = linesPS `liftM` mReadFilePS f One instance of this class is IO, but I can also have instances for in-memory data structures (outside the IO monad) or (or example) for reading a tarball from disk--which would be a monad that acts within the IO monad. -- David Roundy http://www.darcs.net

On Sun, Feb 13, 2005 at 08:58:29AM -0500, David Roundy wrote:
I've been working on a typeclass that derives from MonadPlus which will encapsulate certain kinds of IO. With MonadPlus, you can write monadic code with exceptions and everything that may not be executed in the IO monad. You just use fail to throw exceptions, and mplus to catch them.
class MonadPlus m => ReadableDirectory m where mInCurrentDirectory :: FilePath -> m a -> m a mGetDirectoryContents :: m [FilePath] mReadFilePS :: FilePath -> m PackedString mReadFilePSs :: FilePath -> m [PackedString] mReadFilePSs f = linesPS `liftM` mReadFilePS f
One instance of this class is IO, but I can also have instances for in-memory data structures (outside the IO monad) or (or example) for reading a tarball from disk--which would be a monad that acts within the IO monad.
According to http://www.haskell.org/hawiki/MonadPlus (see also the recent thread about MonadPlus) a MonadPlus instance should obey m >> mzero === mzero, which IO doesn't. IOW, the MonadPlus instance for IO (defined in Control.Monad.Error) probably shouldn't be there. Groeten, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

On Sun, Feb 13, 2005 at 04:57:46PM +0100, Remi Turk wrote:
According to http://www.haskell.org/hawiki/MonadPlus (see also the recent thread about MonadPlus) a MonadPlus instance should obey m >> mzero === mzero, which IO doesn't. IOW, the MonadPlus instance for IO (defined in Control.Monad.Error) probably shouldn't be there.
True. In the IO monad there are side effects that don't get "erased" when a later action raises an exception as that law would suggest. But any IO-like monad that I'm likely to implement will have the same discrepancy, and in any IO code that catches "enough" exceptions to be bug-free will be immune to this issue. Basically, the issue is that do { writeFile "foo" "bar"; writeFile "bar" "foo" } `catch` \_ -> putStr "Couldn't create file\m" may reach the putStr with or without the file "foo" existing, and there's no way to know whether or not it was created. But that just means the code was written sloppily--that is, if the existence of that foo file is important. In my uses of MonadPlus, I'd have other schemes essentially immitating IO, so they'd duplicate this behavior (later errors don't undo earlier actions), and well-written functions would depend on that. It might be interesting to write a "backtracking" IO-like monad which obeyed m >> mzero === mzero. I imagine you could do it for something like an ACID database, if you define === as meaning "has the same final result on the database", which of course would only be useful if the database had sufficient locking that it couldn't have been read between the original m and the later mzero. -- David Roundy http://www.darcs.net

On Sun, Feb 13, 2005 at 01:31:56PM -0500, David Roundy wrote:
On Sun, Feb 13, 2005 at 04:57:46PM +0100, Remi Turk wrote:
According to http://www.haskell.org/hawiki/MonadPlus (see also the recent thread about MonadPlus) a MonadPlus instance should obey m >> mzero === mzero, which IO doesn't. IOW, the MonadPlus instance for IO (defined in Control.Monad.Error) probably shouldn't be there.
True. In the IO monad there are side effects that don't get "erased" when a later action raises an exception as that law would suggest. But any IO-like monad that I'm likely to implement will have the same discrepancy, and in any IO code that catches "enough" exceptions to be bug-free will be immune to this issue.
Basically, the issue is that
do { writeFile "foo" "bar"; writeFile "bar" "foo" } `catch` \_ -> putStr "Couldn't create file\m"
may reach the putStr with or without the file "foo" existing, and there's no way to know whether or not it was created. But that just means the code was written sloppily--that is, if the existence of that foo file is important.
In my uses of MonadPlus, I'd have other schemes essentially immitating IO, so they'd duplicate this behavior (later errors don't undo earlier actions), and well-written functions would depend on that.
But what if `instance MonadPlus IO' disappears from the libraries some day? (which it should, IMO)
It might be interesting to write a "backtracking" IO-like monad which obeyed m >> mzero === mzero. I imagine you could do it for something like an ACID database, if you define === as meaning "has the same final result on the database", which of course would only be useful if the database had sufficient locking that it couldn't have been read between the original m and the later mzero.
You might be interested in the recent STM monad then (Control.Concurrent.STM in GHC-6.4): `T' for Transactional. However, though it supports both MonadPlus and exceptions, it doesn't use MonadPlus for exceptions: It's used for blocking/retrying a thread/transaction. I never used it, so I'm not sure whether it makes any sense, but wouldn't MonadError be a better candidate class to base it upon? Greetings, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

On Sun, Feb 13, 2005 at 08:06:36PM +0100, Remi Turk wrote:
You might be interested in the recent STM monad then (Control.Concurrent.STM in GHC-6.4): `T' for Transactional. However, though it supports both MonadPlus and exceptions, it doesn't use MonadPlus for exceptions: It's used for blocking/retrying a thread/transaction.
And for non-deterministic choice. BTW, I have an implementation of STM based entirely on old concurrency primitives, which means that it will work in older GHC and probably in other Haskell compilers. I am going to put it on my web site, when I get one. Best regards Tomasz -- Szukamy programisty C++ i Haskell'a: http://tinyurl.com/5mw4e

On Sun, Feb 13, 2005 at 09:28:18PM +0100, Tomasz Zielonka wrote:
On Sun, Feb 13, 2005 at 08:06:36PM +0100, Remi Turk wrote:
You might be interested in the recent STM monad then (Control.Concurrent.STM in GHC-6.4): `T' for Transactional. However, though it supports both MonadPlus and exceptions, it doesn't use MonadPlus for exceptions: It's used for blocking/retrying a thread/transaction.
And for non-deterministic choice.
BTW, I have an implementation of STM based entirely on old concurrency primitives, which means that it will work in older GHC and probably in other Haskell compilers. I am going to put it on my web site, when I get one.
Best regards Tomasz
Cool :) Is it actually race/deadlock/othergeneralnastiness-free? (as the paper claims that e.g. mergeIO :: [IO a] -> IO a is unimplementable in anything built on mutexes and condition variables.) -- Nobody can be exactly like me. Even I have trouble doing it.

On Sun, Feb 13, 2005 at 10:25:49PM +0100, Remi Turk wrote:
BTW, I have an implementation of STM based entirely on old concurrency primitives, which means that it will work in older GHC and probably in other Haskell compilers. I am going to put it on my web site, when I get one.
Cool :) Is it actually race/deadlock/othergeneralnastiness-free?
It should be, but there may be bugs of course. I know there are some possible space leaks, but that's also fixable.
(as the paper claims that e.g. mergeIO :: [IO a] -> IO a is unimplementable in anything built on mutexes and condition variables.)
My STM monad is not IO, it has the same restrictions as STM in the paper. The paper doesn't claim you can't implement mergeSTM :: [STM a] -> STM a mergeSTM = msum Also, the STM in GHC 6.4 is written in C. Do you think that Haskell's IO monad lacks some things needed to write this thing? I can tell you there are some problems with types, but they can be solved in a more or less standard way. Best regards Tomasz -- Szukamy programisty C++ i Haskell'a: http://tinyurl.com/5mw4e

On Sun, Feb 13, 2005 at 10:33:06PM +0100, Tomasz Zielonka wrote:
On Sun, Feb 13, 2005 at 10:25:49PM +0100, Remi Turk wrote:
BTW, I have an implementation of STM based entirely on old concurrency primitives, which means that it will work in older GHC and probably in other Haskell compilers. I am going to put it on my web site, when I get one.
Cool :) Is it actually race/deadlock/othergeneralnastiness-free?
It should be, but there may be bugs of course. I know there are some possible space leaks, but that's also fixable.
(as the paper claims that e.g. mergeIO :: [IO a] -> IO a is unimplementable in anything built on mutexes and condition variables.)
My STM monad is not IO, it has the same restrictions as STM in the paper. The paper doesn't claim you can't implement mergeSTM :: [STM a] -> STM a mergeSTM = msum
Ugh, I should've read what I copied... *nitpick* in the paper merge is defined using foldr1, which errors when given an empty list, as opposed to msum, which merely retries.
Also, the STM in GHC 6.4 is written in C. Do you think that Haskell's IO monad lacks some things needed to write this thing? I can tell you there are some problems with types, but they can be solved in a more or less standard way.
Best regards Tomasz
I don't, though I'm probably not qualified to vote ;) Groeten, Remi P.S. And don't forget to post a link when you put it online. -- Nobody can be exactly like me. Even I have trouble doing it.

On Sun, Feb 13, 2005 at 11:25:07PM +0100, Remi Turk wrote:
(as the paper claims that e.g. mergeIO :: [IO a] -> IO a is unimplementable in anything built on mutexes and condition variables.)
My STM monad is not IO, it has the same restrictions as STM in the paper. The paper doesn't claim you can't implement mergeSTM :: [STM a] -> STM a mergeSTM = msum
P.S. And don't forget to post a link when you put it online.
Here is the darcs repository: http://www.uncurry.com/repos/FakeSTM/ Warning: no documentation (other than patch comments), probably some bugs Best regards Tomasz

G'day all.
Quoting David Roundy
It might be interesting to write a "backtracking" IO-like monad which obeyed m >> mzero === mzero. I imagine you could do it for something like an ACID database, if you define === as meaning "has the same final result on the database", which of course would only be useful if the database had sufficient locking that it couldn't have been read between the original m and the later mzero.
You should talk to the logic programming community about this some time. As Lee Naish has pointed out on many occasions, it would involve finding a way to insert the page back into the laser printer and lift the toner off. Cheers, Andrew Bromage

On Sun, Feb 13, 2005 at 06:05:23PM -0500, ajb@spamcop.net wrote:
G'day all.
Quoting David Roundy
: It might be interesting to write a "backtracking" IO-like monad which obeyed m >> mzero === mzero. I imagine you could do it for something like an ACID database, if you define === as meaning "has the same final result on the database", which of course would only be useful if the database had sufficient locking that it couldn't have been read between the original m and the later mzero.
You should talk to the logic programming community about this some time.
As Lee Naish has pointed out on many occasions, it would involve finding a way to insert the page back into the laser printer and lift the toner off.
That's why it would only be possible in a limited realm such as a database, where you could "quarantine" the changes using locking, and where you could define strictly define "equality" in the world in which the IO takes place. It basically would just require a journalling system, which I imagine most decent databases provide in order to give ACID behavior. I'm far from a database expert, but this is how I understand that these things work. -- David Roundy http://www.darcs.net

ajb@spamcop.net wrote:
G'day all.
Quoting David Roundy
: It might be interesting to write a "backtracking" IO-like monad which obeyed m >> mzero === mzero. I imagine you could do it for something like an ACID database, if you define === as meaning "has the same final result on the database", which of course would only be useful if the database had sufficient locking that it couldn't have been read between the original m and the later mzero.
You should talk to the logic programming community about this some time.
As Lee Naish has pointed out on many occasions, it would involve finding a way to insert the page back into the laser printer and lift the toner off.
Not quite... remember the IO monad is a function which returns an IO program... as long as none of the IO program has been executed it is possible to 'edit' the program to remove parts... The problem only really occurs in interactive programs, where input forces partial evaluation of the function result... once the function has been evaluated up to the input the output so far cannot be retracted. Keean.

G'day all.
Quoting Remi Turk
According to http://www.haskell.org/hawiki/MonadPlus (see also the recent thread about MonadPlus) a MonadPlus instance should obey m >> mzero === mzero, which IO doesn't. IOW, the MonadPlus instance for IO (defined in Control.Monad.Error) probably shouldn't be there.
Clearly the wiki page has not been updated to reflect the current debate. :-) I've changed the wording to this. Anyone disagree? Note: There are theoretical reasons why ''mzero'' should be a right-zero for (>>=), but surprisingly few of the existing MonadPlus instances actually obey this law. {{{IO}}} does not, and neither do any ["MonadTransformer"]s, since they may be stacked on top of {{{IO}}}. This suggests that either some of the extant MonadPlus instances are inappropriate, or that the law itself might be incorrect. There is continuing debate over this, and the dust has not yet settled. Cheers, Andrew Bromage

On Sun, 13 Feb 2005 17:59:57 -0500, ajb@spamcop.net
G'day all.
Quoting Remi Turk
: According to http://www.haskell.org/hawiki/MonadPlus (see also the recent thread about MonadPlus) a MonadPlus instance should obey m >> mzero === mzero, which IO doesn't. IOW, the MonadPlus instance for IO (defined in Control.Monad.Error) probably shouldn't be there.
Clearly the wiki page has not been updated to reflect the current debate. :-)
I've changed the wording to this. Anyone disagree?
Note: There are theoretical reasons why ''mzero'' should be a right-zero for (>>=), but surprisingly few of the existing MonadPlus instances actually obey this law. {{{IO}}} does not, and neither do any ["MonadTransformer"]s, since they may be stacked on top of {{{IO}}}. This suggests that either some of the extant MonadPlus instances are inappropriate, or that the law itself might be incorrect. There is continuing debate over this, and the dust has not yet settled.
I think it's unfair to the monad transformers to simply say that they don't obey the law. The interesting thing is whether they *preserve* the law. A monad transformer T preserves a law if given a monad M which obeys the law holds then the monad T M obeys the law. I haven't checked if this is the case for any of the monad transformers in the hierarchical libraries though. But I think that the wording should be changed so that they aren't blamed for breaking the law. (I can't believe I'm taking sides with monad transformers as if they where human. I spend too much time hacking haskell I guess...) /Josef

G'day all.
Quoting Josef Svenningsson
I think it's unfair to the monad transformers to simply say that they don't obey the law. The interesting thing is whether they *preserve* the law. A monad transformer T preserves a law if given a monad M which obeys the law holds then the monad T M obeys the law.
The law in question is that mzero is a right-zero for bind. How can an underlying monad be said to "obey" this law if it doesn't support mzero? Cheers, Andrew Bromage

On Sun, 13 Feb 2005 19:08:26 -0500, ajb@spamcop.net
Quoting Josef Svenningsson
: I think it's unfair to the monad transformers to simply say that they don't obey the law. The interesting thing is whether they *preserve* the law. A monad transformer T preserves a law if given a monad M which obeys the law holds then the monad T M obeys the law.
The law in question is that mzero is a right-zero for bind. How can an underlying monad be said to "obey" this law if it doesn't support mzero?
You're of course absolutely right that it doesn't make sense to talk about mzero being a right-identity for bind if the monad doesn't support mzero. I should have been more clear. Let me have another try at explaining myself. Let's consider a specific monad transformer, say (ReaderT r). What I hope to convince you of is that (ReaderT r) cannot be said break the mzero-is-right-identity-for-bind law. Now, if we look at the MonadPlus instance for (ReaderT r) it looks like this: \begin{code} instance (MonadPlus m) => MonadPlus (ReaderT r m) where mzero = ReaderT $ \_ -> mzero m `mplus` n = ReaderT $ \r -> runReaderT m r `mplus` runReaderT n r \end{code} This important thing to note here is that the above instance declaration relies on an underlying monad m with mzero and mplus. If we try (and indeed succeed) to prove that (ReaderT r m) satisfies the mzero-is-right-identity-for-bind law we will see that the proof depend crucially on the fact that m also obeys the law. This is the best that the monad transformer can do, namely to preserve the law. You claimed that monad transformers break the mzero-is-right-identity-for-bind law because they can be applied to IO. I say, it's not the monad transformers fault. They cannot possibly be expected to repair the law if they are given a faulty monad. I hope this makes things a little clearer. /Josef

Josef Svenningsson
You claimed that monad transformers break the mzero-is-right-identity-for-bind law because they can be applied to IO. I say, it's not the monad transformers fault. They cannot possibly be expected to repair the law if they are given a faulty monad.
I agree. They as well could be said to break the core monad laws. It's not their fault. -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/

G'day all.
Quoting Marcin 'Qrczak' Kowalczyk
I agree. They as well could be said to break the core monad laws. It's not their fault.
I disagree. This: instance (Monad m) => Monad (TransformerT m) says that if m satisfies the requirements of a Monad (including the core laws), then TransformerT m does too. Many people have written monad transformers which obey this rule. This, on the other hand: instance (Monad m) => MonadPlus (NondetT m) says that if m satisfies the requirements of a Monad (including the core laws), then NondetT m satisfies the requirements of a MonadPlus (including the laws). If you include the "mzero is a right zero for bind" law as a requirement for MonadPlus, then such a transformer cannot exist. Existing implementations (e.g. from Ralf Hinze's paper) break the MonadPlus laws. So what to do? Off the top of my head: 1. Determine what those extra requirements are, and wrap them up in a typeclass. Disallow NondetT from being built on top of monads like IO, because they break the third law. (Not an option, since NondetT IO is so useful.) 2. Make a class like MonadPlus, with precisely the same operations as MonadPlus, only without the third law. (This option brought to you by the Department of Redundancy Department.) 3. Drop the law as a requirement. (My preferred option, obviously!) Cheers, Andrew Bromage

Josef Svenningsson
You claimed that monad transformers break the mzero-is-right-identity-for-bind law because they can be applied to IO. I say, it's not the monad transformers fault. They cannot possibly be expected to repair the law if they are given a faulty monad.
Doesn't that argue for allowing proven and unproven Monads in Haskell? Using the Curry-Howard correspondance, wouldn't it make sense to provide (proof) terms in a Monad's signature that are witnesses for the monad laws? One could then have signature-only Monads (ie a rather weak requirement) and signature+laws Monads (much stronger). Jacques

On Mon, 14 Feb 2005 10:07:41 -0500, Jacques Carette
Josef Svenningsson
wrote: You claimed that monad transformers break the mzero-is-right-identity-for-bind law because they can be applied to IO. I say, it's not the monad transformers fault. They cannot possibly be expected to repair the law if they are given a faulty monad.
Doesn't that argue for allowing proven and unproven Monads in Haskell?
I believe you misunderstand me. The point that I was trying to make was about monad transformers. I was saying that the best they can do with respect to a law is to preserve it, which I believe all monad transformers should do. Otherwise they don't deserve the name. Turning to monad they should certainly fulfil the laws we associate with a monad. Otherwise they wouldn't be monads! I am not proposing or encouraging that one should declare a data type an instance of monad if they do not obey the monad laws. Cheers, /Josef

G'day all.
Quoting Josef Svenningsson
You're of course absolutely right that it doesn't make sense to talk about mzero being a right-identity for bind if the monad doesn't support mzero. I should have been more clear. Let me have another try at explaining myself.
OK.
Let's consider a specific monad transformer, say (ReaderT r). What I hope to convince you of is that (ReaderT r) cannot be said break the mzero-is-right-identity-for-bind law.
Yep, I'd agree with that. The important thing is this instance: instance (MonadPlus m) => MonadPlus (ReaderT r m) This says that if m is a MonadPlus (we'll assume for a moment that this includes the "mzero is a right zero for bind" law), then ReaderT r m is a MonadPlus (including the same law). I was thinking more along the lines of Ralf Hinze's nondeterminism transformer monad: http://haskell.org/hawiki/NonDeterminism The relevant instance is this: instance (Monad m) => MonadPlus (NondetT m) That is, if m is a Monad, then NondetT m is a MonadPlus. This is not true if a requirement for MonadPlus is that it include the "mzero is a right zero for bind" law. Indeed, such a transformer is impossible to write if that law is a requirement.
You claimed that monad transformers break the mzero-is-right-identity-for-bind law because they can be applied to IO. I say, it's not the monad transformers fault. They cannot possibly be expected to repair the law if they are given a faulty monad.
IO is not a faulty monad. It satisfies all of the laws that a monad is supposed to satisfy. Cheers, Andrew Bromage

On Mon, 14 Feb 2005 19:01:53 -0500, ajb@spamcop.net
I was thinking more along the lines of Ralf Hinze's nondeterminism transformer monad:
http://haskell.org/hawiki/NonDeterminism
The relevant instance is this:
instance (Monad m) => MonadPlus (NondetT m)
That is, if m is a Monad, then NondetT m is a MonadPlus. This is not true if a requirement for MonadPlus is that it include the "mzero is a right zero for bind" law. Indeed, such a transformer is impossible to write if that law is a requirement.
Ah, I see. You are quite right.
You claimed that monad transformers break the mzero-is-right-identity-for-bind law because they can be applied to IO. I say, it's not the monad transformers fault. They cannot possibly be expected to repair the law if they are given a faulty monad.
IO is not a faulty monad. It satisfies all of the laws that a monad is supposed to satisfy.
Sloppy terminology on my side again. What I meant to say is that any MonadPlus instance of IO is faulty if we insist on the mzero-is-right-identity-for-bind law. I agree with you that the law should be dropped. Cheers, /Josef

Technically this is a use of MonadError, not MonadPlus (see earlier discussion about how IO is _not_ an instance of MonadPlus). Keean. David Roundy wrote:
On Sat, Feb 12, 2005 at 01:08:59PM -0500, Benjamin Pierce wrote:
I have seen lots of examples that show how it's useful to make some type constructor into an instance of Monad.
Where can I find examples showing why it's good to take the trouble to show that something is also a MonadPlus? (I know there are many examples of things that *are* MonadPluses; what I want to know is why this is interesting. :-)
I've been working on a typeclass that derives from MonadPlus which will encapsulate certain kinds of IO. With MonadPlus, you can write monadic code with exceptions and everything that may not be executed in the IO monad. You just use fail to throw exceptions, and mplus to catch them.
class MonadPlus m => ReadableDirectory m where mInCurrentDirectory :: FilePath -> m a -> m a mGetDirectoryContents :: m [FilePath] mReadFilePS :: FilePath -> m PackedString mReadFilePSs :: FilePath -> m [PackedString] mReadFilePSs f = linesPS `liftM` mReadFilePS f
One instance of this class is IO, but I can also have instances for in-memory data structures (outside the IO monad) or (or example) for reading a tarball from disk--which would be a monad that acts within the IO monad.

Here's an example: In my paper "First Class Patterns" http://citeseer.ist.psu.edu/tullsen00first.html, by defining the pattern combinators using MonadPlus, you get standard pattern matching with the Maybe instance of MonadPlus and you get backtracking pattern matching with the [] (list) instance of MonadPlus. - Mark On Feb 12, 2005, at 10:08 AM, Benjamin Pierce wrote:
I have seen lots of examples that show how it's useful to make some type constructor into an instance of Monad.
Where can I find examples showing why it's good to take the trouble to show that something is also a MonadPlus? (I know there are many examples of things that *are* MonadPluses; what I want to know is why this is interesting. :-)
Thanks,
- Benjamin
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (10)
-
ajb@spamcop.net
-
Benjamin Pierce
-
David Roundy
-
Jacques Carette
-
Josef Svenningsson
-
Keean Schupke
-
Marcin 'Qrczak' Kowalczyk
-
Mark Tullsen
-
Remi Turk
-
Tomasz Zielonka