
Consider the following beautiful code: run :: State -> Foo -> ResultSet State run_and :: State -> Foo -> Foo -> ResultSet State run_and s0 x y = do s1 <- run s0 x s2 <- run s1 y return s2 run_or :: State -> Foo -> Foo -> ResultSet State run_or s0 x y = merge (run s0 x) (run s0 y) That works great. Unfortunately, I made some alterations to the functionallity the program has, and now it is actually possible for 'run' to fail. When this happens, a problem should be reported to the user. (By "user" I mean "the person running my compiled application".) After an insane amount of time making my head hurt, I disocvered that the type "Either ErrorType (ResultSet State)" is actually a monad. (Or rather, a monad within a monad.) Unfortunately, this causes some pretty serious problems: run :: State -> Foo -> Either ErrorType (ResultSet State) run_or :: State -> Foo -> Foo -> Either ErrorType (ResultSet State) run_or s0 x y = do rset1 <- run s0 x rset2 <- run s1 y return (merge rset1 rset2) run_and :: State -> Foo -> Foo -> Either ErrorType (ResultSet State) run_and s0 x y = run s0 x >>= \rset1 -> rset1 >>= \s1 -> run s1 y The 'run_or' function isn't too bad. However, after about an hour of trying, I cannot construct any definition for 'run_and' which actually typechecks. The type signature for (>>=) requires that the result monad matches the source monad, and there is no way for me to implement this. Since ResultSet *just happens* to also be in Functor, I can get as far as run_and s0 x y = run s0 x >>= \rset1 -> fmap (\s1 -> run s1 y) rset1 but that still leaves me with a value of type ResultSet (Either ErrorType (ResultSet State)) and no obvious way to fix this. At this point I am sorely tempted to just change ResultSet to include the error functionallity I need. However, ResultSet is *already* an extremely complicated monad that took me weeks to get working correctly... I'd really prefer to just layer error handling on the top. But I just can't get it to work right. It's soooo fiddly untangling the multiple monads to try to *do* any useful work. Does anybody have any idea how this whole monad stacking craziness is *supposed* to work?

On Thu, 2008-10-02 at 18:18 +0100, Andrew Coppin wrote:
Consider the following beautiful code:
run :: State -> Foo -> ResultSet State
run_and :: State -> Foo -> Foo -> ResultSet State run_and s0 x y = do s1 <- run s0 x s2 <- run s1 y return s2
run_or :: State -> Foo -> Foo -> ResultSet State run_or s0 x y = merge (run s0 x) (run s0 y)
That works great. Unfortunately, I made some alterations to the functionallity the program has, and now it is actually possible for 'run' to fail. When this happens, a problem should be reported to the user. (By "user" I mean "the person running my compiled application".) After an insane amount of time making my head hurt, I disocvered that the type "Either ErrorType (ResultSet State)" is actually a monad.
It's a monad if you can write a function join :: Either ErrorType (ResultSet (Either ErrorType (ResultSet alpha))) -> Either ErrorType (ResultSet alpha) (which follows from being able to write a function interleave :: Either ErrorType (ResultSet alpha) -> ResultSet (Either ErrorType alpha) satisfying certain laws). Otherwise not, as you noticed.
(Or rather, a monad within a monad.) Unfortunately, this causes some pretty serious problems:
run :: State -> Foo -> Either ErrorType (ResultSet State)
run_or :: State -> Foo -> Foo -> Either ErrorType (ResultSet State) run_or s0 x y = do rset1 <- run s0 x rset2 <- run s1 y return (merge rset1 rset2)
run_and :: State -> Foo -> Foo -> Either ErrorType (ResultSet State) run_and s0 x y = run s0 x >>= \rset1 -> rset1 >>= \s1 -> run s1 y
The 'run_or' function isn't too bad. However, after about an hour of trying, I cannot construct any definition for 'run_and' which actually typechecks. The type signature for (>>=) requires that the result monad matches the source monad, and there is no way for me to implement this. Since ResultSet *just happens* to also be in Functor,
It doesn't just happen to be one. liftM is *always* a law-abiding definition for fmap, when used at a law-abiding monad. (This is why posters here are always bringing up head-hurting category theory, btw. Absorbing it sufficiently actually teaches you useful things about Haskell programming.)
I can get as far as
run_and s0 x y = run s0 x >>= \rset1 -> fmap (\s1 -> run s1 y) rset1
but that still leaves me with a value of type ResultSet (Either ErrorType (ResultSet State)) and no obvious way to fix this.
At this point I am sorely tempted to just change ResultSet to include the error functionallity I need. However, ResultSet is *already* an extremely complicated monad that took me weeks to get working correctly...
What does it look like? Quite possibly it can be factored out into smaller pieces using monad transformers. (In which case adding error handling is just sticking in another transformer at the right layer in the stack --- that is, the layer where adding error handling works :).
I'd really prefer to just layer error handling on the top. But I just can't get it to work right. It's soooo fiddly untangling the multiple monads to try to *do* any useful work.
Does anybody have any idea how this whole monad stacking craziness is *supposed* to work?
No. [1] But we know how it *can* work; this is what monad transformers exist to do. You want to either change ResultSet to be a monad transformer, (which can admittedly be a major re-factoring, depending on what exactly ResultSet is doing --- compare http://haskell.org/haskellwiki/ListT_done_right to regular lists), or you want the monad ErrorT ErrorType ResultSet. Very little can be said in general without knowing what ResultSet looks like. jcc [1] I've seen plenty of things that *claim* to be a general solution, but they all seem to boil down to re-implementing everything in terms of State (or State + Cont). I'm not satisfied that's actually the right way to solve these issues.

Jonathan Cast wrote:
On Thu, 2008-10-02 at 18:18 +0100, Andrew Coppin wrote:
After an insane amount of time making my head hurt, I disocvered that the type "Either ErrorType (ResultSet State)" is actually a monad.
It's a monad if you can write a function
join :: Either ErrorType (ResultSet (Either ErrorType (ResultSet alpha))) -> Either ErrorType (ResultSet alpha)
(which follows from being able to write a function
interleave :: Either ErrorType (ResultSet alpha) -> ResultSet (Either ErrorType alpha)
satisfying certain laws). Otherwise not, as you noticed.
Er... OK. Yes, I guess that kind of makes sense...
Since ResultSet *just happens* to also be in Functor,
It doesn't just happen to be one. liftM is *always* a law-abiding definition for fmap, when used at a law-abiding monad.
I'm lost... (What does liftM have to do with fmap?)
(This is why posters here are always bringing up head-hurting category theory, btw. Absorbing it sufficiently actually teaches you useful things about Haskell programming.)
That would be a surprising and unexpected result. After all, knowing about set theory doesn't help you write SQL...
At this point I am sorely tempted to just change ResultSet to include the error functionallity I need. However, ResultSet is *already* an extremely complicated monad that took me weeks to get working correctly...
What does it look like?
A list, basically. (But obviously slightly more complicated than that.)
Quite possibly it can be factored out into smaller pieces using monad transformers. (In which case adding error handling is just sticking in another transformer at the right layer in the stack --- that is, the layer where adding error handling works :).
Well I'm *already* trying to layer an error transformer on the top and it's failing horribly. I don't see how splitting things up even more could do anything but make the program even *more* complex.
Does anybody have any idea how this whole monad stacking craziness is *supposed* to work?
No. [1]
Ah, good. :-)
But we know how it *can* work; this is what monad transformers exist to do. You want to either change ResultSet to be a monad transformer, or you want the monad ErrorT ErrorType ResultSet. Very little can be said in general without knowing what ResultSet looks like.
I thought ErrorT was a class name...?

Andrew Coppin wrote:
I thought ErrorT was a class name...?
No, it's the name of the error monad transformer type. "Error" is just an ordinary monad, it's ErrorT that's the transformer. So it sounds like the answer to your question below:
You could try using an exception monad transformer here
I thought I already was?
...is no, you weren't. You need to construct your monad stack using ErrorT, not Error. Anton

--- On Thu, 10/2/08, Andrew Coppin
I'm lost...
(What does liftM have to do with fmap?)
They're (effectively) the same function. i.e. liftM :: (Monad m) => (a -> b) -> m a -> m b fmap :: (Functor f) => (a -> b) -> f a -> f b liftM turns a function from a to b into a function from m a to m b; fmap turns a function from a to b into a function from f a to f b; If your datatype with a Monad instance also has a Functor instance (which it *can* have, you just need to declare the instance), then liftM is equivalent to fmap.

Robert Greayer wrote:
--- On Thu, 10/2/08, Andrew Coppin
wrote: I'm lost...
(What does liftM have to do with fmap?)
They're (effectively) the same function.
i.e.
liftM :: (Monad m) => (a -> b) -> m a -> m b fmap :: (Functor f) => (a -> b) -> f a -> f b
Hmm. Interesting. I hadn't thought of it like that...

If your datatype with a Monad instance also has a Functor instance (which it *can* have, you just need to declare the instance), then liftM is equivalent to fmap.
Only if you ignore efficiency issues, of course. Some monads have an fmap which is significantly faster than bind. liftM f m = do a <- m return (f a) Consider []; this becomes liftM f m = m >>= \a -> return (f a) = concatMap (\a -> [f a]) m which, in the absence of other optimizations, is going to do a lot more allocation and branching than fmap fmap f m = map f m -- ryan

On Thu, 2008-10-02 at 20:53 +0100, Andrew Coppin wrote:
Jonathan Cast wrote:
On Thu, 2008-10-02 at 18:18 +0100, Andrew Coppin wrote:
After an insane amount of time making my head hurt, I disocvered that the type "Either ErrorType (ResultSet State)" is actually a monad.
It's a monad if you can write a function
join :: Either ErrorType (ResultSet (Either ErrorType (ResultSet alpha))) -> Either ErrorType (ResultSet alpha)
(which follows from being able to write a function
interleave :: Either ErrorType (ResultSet alpha) -> ResultSet (Either ErrorType alpha)
satisfying certain laws). Otherwise not, as you noticed.
Er... OK. Yes, I guess that kind of makes sense...
Since ResultSet *just happens* to also be in Functor,
It doesn't just happen to be one. liftM is *always* a law-abiding definition for fmap, when used at a law-abiding monad.
I'm lost...
(What does liftM have to do with fmap?)
OK, I'll try again. If I have a Haskell type constructor m, and m has a law-abiding instance of Monad, then instance Functor m where fmap = liftM is *always* a law-abiding instance of Functor. Furthermore, if m is an instance of Functor, then according to the Haskell report, fmap = liftM is one of the monad laws.
(This is why posters here are always bringing up head-hurting category theory, btw. Absorbing it sufficiently actually teaches you useful things about Haskell programming.)
That would be a surprising and unexpected result.
It also happens to be true. Most computer-related technologies started as engineering solutions, and pulled in mathematical concepts mostly when those concepts managed to inspire vaguely similar engineering solutions. Haskell doesn't have that kind of heritage; its ultimate ancestor is ML, which was originally a component of a theorem-proving system, and its design has traditionally been (despite denials) about pulling concepts from math directly into programming.
After all, knowing about set theory doesn't help you write SQL...
SQL has an extremely tenuous relationship to set theory. Set theory can sometimes inspire SQL database design, and it can excuse features that would otherwise just be weird, but mostly SQL queries return lists, not sets.
At this point I am sorely tempted to just change ResultSet to include the error functionallity I need. However, ResultSet is *already* an extremely complicated monad that took me weeks to get working correctly...
What does it look like?
A list, basically. (But obviously slightly more complicated than that.)
Nuts. We know how to turn [] into a real monad transformer, but it's ugly. Nevertheless, if you could post the actual type definition, it might make this easier to do.
Quite possibly it can be factored out into smaller pieces using monad transformers. (In which case adding error handling is just sticking in another transformer at the right layer in the stack --- that is, the layer where adding error handling works :).
Well I'm *already* trying to layer an error transformer on the top and it's failing horribly.
Right. The most global property of the system goes with the monad transfomer on bottom.
I don't see how splitting things up even more could do anything but make the program even *more* complex.
Your problem isn't complexity, it's that the monad transformer that goes on top isn't implemented as one (so it wants to go on bottom). Re-factoring might make it easier to generalize that problem away. Or not.
Does anybody have any idea how this whole monad stacking craziness is *supposed* to work?
No. [1]
Ah, good. :-)
But we know how it *can* work; this is what monad transformers exist to do. You want to either change ResultSet to be a monad transformer, or you want the monad ErrorT ErrorType ResultSet. Very little can be said in general without knowing what ResultSet looks like.
I thought ErrorT was a class name...?
No. It's a (higher-order) type constructor. jcc

On Thu, Oct 02, 2008 at 06:18:19PM +0100, Andrew Coppin wrote:
run :: State -> Foo -> Either ErrorType (ResultSet State)
run_and :: State -> Foo -> Foo -> Either ErrorType (ResultSet State) {- some Either-ified version of run_and :: State -> Foo -> Foo -> ResultSet State run_and s0 x y = do s1 <- run s0 x s2 <- run s1 y return s2 -}
I'll assume for simplicity and concreteness that ResultSet = [].
The 'run_or' function isn't too bad. However, after about an hour of trying, I cannot construct any definition for 'run_and' which actually typechecks. The type signature for (>>=) requires that the result monad matches the source monad, and there is no way for me to implement this.
That's right. The type mismatches are telling you that there's a situation you haven't thought about, or at least, haven't told us how you want to handle. Suppose run s0 x = Right [s1a, s1b, s1c] and run s1a y = Left err, run s1b = Right [s2], run s1c = Left err'. What should the overall result of run_and s0 x y be? Somehow you have to choose whether it's a Left or a Right, and which error to report in the former case. For the [] monad, there is a natural way to make this choice: it's encoded in the function sequence :: Monad m => [m a] -> m [a], where in this setting m = Either ErrorType. For your problem, it would probably be a good start to write an instance of Traversable for the ResultSet monad. In general, one way to make the composition of two monads m and n into a monad is to write a function n (m a) -> m (n a); this is the sequence method of a Traversable instance for n. Then you can write join :: m (n (m (n a))) -> m (n a) as m (n (m (n a))) --- fmap sequence ---> m (m (n (n a))) ------ join ---------> m (n (n a)) ------ join ---------> m (n a). Regards, Reid Barton

Reid Barton wrote:
I'll assume for simplicity and concreteness that ResultSet = [].
It more or less is. (But with a more complex internal structure, and correspondingly more complex (>>=) implementation.)
That's right. The type mismatches are telling you that there's a situation you haven't thought about, or at least, haven't told us how you want to handle. Suppose run s0 x = Right [s1a, s1b, s1c] and run s1a y = Left err, run s1b = Right [s2], run s1c = Left err'. What should the overall result of run_and s0 x y be? Somehow you have to choose whether it's a Left or a Right, and which error to report in the former case.
For the [] monad, there is a natural way to make this choice: it's encoded in the function sequence :: Monad m => [m a] -> m [a], where in this setting m = Either ErrorType.
Yeah, while testing I accidentally got a definition that typechecks only because I was using [] as a dummy standin for ResultSet. (Rather than the real implementation.) The sequence function appears to define the basic functionallity I'm after.
For your problem, it would probably be a good start to write an instance of Traversable for the ResultSet monad.
Wuh? What's Traversable?
In general, one way to make the composition of two monads m and n into a monad is to write a function n (m a) -> m (n a); this is the sequence method of a Traversable instance for n.
Oh, *that's* Traversable? Mind you, looking at Data.Traversable, it demands instances for something called "Foldable" first (plus Functor, which I already happen to have). (Looking up Foldable immediately meantions something called "Monoid"... I'm rapidly getting lost here.)
Then you can write join :: m (n (m (n a))) -> m (n a) as
m (n (m (n a))) --- fmap sequence ---> m (m (n (n a))) ------ join ---------> m (n (n a)) ------ join ---------> m (n a).
Um... OK. Ouch. :-S

Andrew Coppin wrote:
Wuh? What's Traversable?
In general, one way to make the composition of two monads m and n into a monad is to write a function n (m a) -> m (n a); this is the sequence method of a Traversable instance for n.
Oh, *that's* Traversable?
Mind you, looking at Data.Traversable, it demands instances for something called "Foldable" first (plus Functor, which I already happen to have).
(Looking up Foldable immediately meantions something called "Monoid"... I'm rapidly getting lost here.)
It sounds like you've figured things out now, but just to chime in. The
problem is that there are a number of different type classes that all
tackle different perspectives on the same thing, or rather, slightly
different things.
These things ---Foldable, Traversable, Monoid, Functor, Applicative,
Monad, MonadPlus, MonadLogic--- they each capture certain basic concepts
that apply to the majority of "normal" data structures. In a very real
sense, these patterns are the core of what category theory is about. And
yet, if you were to try to draw out a venn diagram for them, you'd end
up with something that looks more like a lotus[1] than an OO hierarchy.
For each of these type classes, having one or two of them implies having
many of the rest, regardless of which two you start with. And yet, they
are all different and there are examples of reasonable data structures
which lack one or more of these properties. This circularity makes it
hard to figure out where to even begin. In category theory terminology,
a monad is a monoid on the category of endo-functors. Similarly, list is
the free monoid on any set. Even if you don't grok the terminology,
seeing some of this circularity in definitions should give perspective
on why there's such a tangled mess of type classes.
Ultimately, each of these classes is trying to answer the question: what
is a function? Often it's not helpful to discuss arbitrary functions,
but thankfully most of the functions we're interested in are in fact
very well behaved, and these classes capture the families of structure
we find in those functions. Data structures too can be thought of as
functions, and their mathematical structures are often just as well behaved.
To start in the middle, every Monad is also an Applicative functor and
every Applicative is also a Functor. The situation is actually more
complicated than that since a monad can give rise to more than one
functor (and I believe applicative functors do the same), but it's a
good approximation to start with. If the backwards compatibility issues
could be resolved, it'd be nice to clean up these three classes by
making a type-class hierarchy out of them. (Doing a good job of it would
be helped by some tweaks in how type classes are declared, IMO.)
MonadPlus is for Monads which are also monoids. If you're familiar with
semirings, you can think of (>>=) as conjunction and `mplus` as
representing choice. As others've said, an important distinction is that
MonadPlus universally quantifies over the 'elements' in the monad,
whereas Monoid doesn't. This means that the monoidal behavior of
MonadPlus is a property of the structure of the monad itself, rather
than a property of the elements it contains or an interaction between
the two. In a similar vein is MonadLogic which is a fancier name for
lists or nondeterminism.
Foldable and Traversable are more datastructure-oriented, though they
can be for abstract types (i.e. functions). Foldable is for structures
than can be consumed in an orderly fashion, and Traversable is for
structures that can be reconstructed. A minimal definition for
Traversable gives you a function |t (f a) -> f (t a)| that lets you
distribute the structure over any functor. With that function alone, you
can define instances for Foldable and Functor; conversely, with Foldable
and Functor you can usually write such a function. In some cases, this
is too stringent a requirement since you may be able to distribute
particular

On Thu, Oct 2, 2008 at 1:18 PM, Andrew Coppin
At this point I am sorely tempted to just change ResultSet to include the error functionallity I need. However, ResultSet is *already* an extremely complicated monad that took me weeks to get working correctly... I'd really prefer to just layer error handling on the top. But I just can't get it to work right. It's soooo fiddly untangling the multiple monads to try to *do* any useful work.
Does anybody have any idea how this whole monad stacking craziness is *supposed* to work?
In general, monads don't compose. That is, there's no foolproof way to
take two monads m1 and m2 and create a third monad m3 which does
everything m1 and m2 does. People mostly get around that by using
monad transformers.
You could try using an exception monad transformer here, but that
won't give you the same semantics. "ErrorT ErrorType ResultSet a" is
isomorphic to "ResultSet (Either ErrorType a)".
If you must have something equivalent to Either ErrorType (ResultSet
a), you either need to (1) redesign ResultSet to include error
handling, (2) redesign ResultSet to be a monad transformer, or (3)
restrict yourself to the operations in Applicative.
Option (3) works because applicative functors *do* compose. (Also,
every instance of Monad is trivially an instance of Applicative.)
--
Dave Menendez

David Menendez wrote:
In general, monads don't compose. That is, there's no foolproof way to take two monads m1 and m2 and create a third monad m3 which does everything m1 and m2 does. People mostly get around that by using monad transformers.
...OK then.
You could try using an exception monad transformer here
I thought I already was? At least, I spent about an hour reading through Control.Monad.Error trying to figure out what the hell is going on, and eventually arrived at a type signature that represents what I'm trying to do and seems to be accepted as a monad. But I can't define a working AND function with it. :-( I was under the impression that you can stack monad transformers on top of each other and get it to work, but it doesn't seem to want to work for me...
but that won't give you the same semantics. "ErrorT ErrorType ResultSet a" is isomorphic to "ResultSet (Either ErrorType a)".
Hmm. That would be something quite different. Either the entire computation fails returning a reason why, or it produces a normal result set.
If you must have something equivalent to Either ErrorType (ResultSet a), you either need to (1) redesign ResultSet to include error handling, (2) redesign ResultSet to be a monad transformer, or (3) restrict yourself to the operations in Applicative.
Option (3) works because applicative functors *do* compose. (Also, every instance of Monad is trivially an instance of Applicative.)
Uh... what's Applicative? (I had a look at Control.Applicative, but it just tells me that it's "a strong lax monoidal functor". Which isn't very helpful, obviously.)

Hi Andrew, Andrew Coppin wrote:
Uh... what's Applicative? (I had a look at Control.Applicative, but it just tells me that it's "a strong lax monoidal functor". Which isn't very helpful, obviously.)
Seriously, what are you talking about? The haddock page for Control.Applicative hoogle links to begins with
This module describes a structure intermediate between a functor and a monad: it provides pure expressions and sequencing, but no binding. (Technically, a strong lax monoidal functor.) For more details, see Applicative Programming with Effects, by Conor McBride and Ross Paterson, online at http://www.soi.city.ac.uk/~ross/papers/Applicative.html.
This interface was introduced for parsers by Niklas Röjemo, because it admits more sharing than the monadic interface. The names here are mostly based on recent parsing work by Doaitse Swierstra.
This class is also useful with instances of the Traversable class.
I agree that this is hard to understand, but it's more then just "strong lax monoidal functor", isn't it? More importantly, there is a reference to a wonderful and easy to read paper. (easy in the "easy for Haskell programmers" sense, not in the "easy for the authors, and maybe the inventors of Haskell" sense). Just give it a try. Just in case you missed the link for some reason, here is it again: http://www.soi.city.ac.uk/~ross/papers/Applicative.html Tillmann PS. Regarding Applicative, you may be interested in the original proposal introducing it, which can be found here: http://www.soi.city.ac.uk/~ross/papers/Applicative.html PPS. Don't miss McBride's and Peterson's great paper about applicative functors at http://www.soi.city.ac.uk/~ross/papers/Applicative.html. PPPS. You may also be interested in http://www.soi.city.ac.uk/~ross/papers/Applicative.pdf. PPPPS. If you wonder what do to next when visiting http://www.soi.city.ac.uk/~ross/papers/Applicative.html, you could consider clicking on the link to http://www.soi.city.ac.uk/~ross/papers/Applicative.pdf. Its a very interesting paper, well, actually, it reads more like a tutorial. Just like a blog post, but so much better then the usual blog post.

Tillmann Rendel wrote:
Seriously, what are you talking about? The haddock page for Control.Applicative hoogle links to begins with
This module describes a structure intermediate between a functor and a monad: it provides pure expressions and sequencing, but no binding. (Technically, a strong lax monoidal functor.) For more details, see Applicative Programming with Effects, by Conor McBride and Ross Paterson, online at http://www.soi.city.ac.uk/~ross/papers/Applicative.html.
This interface was introduced for parsers by Niklas Röjemo, because it admits more sharing than the monadic interface. The names here are mostly based on recent parsing work by Doaitse Swierstra.
This class is also useful with instances of the Traversable class.
I agree that this is hard to understand, but it's more then just "strong lax monoidal functor", isn't it? More importantly, there is a reference to a wonderful and easy to read paper. (easy in the "easy for Haskell programmers" sense, not in the "easy for the authors, and maybe the inventors of Haskell" sense). Just give it a try.
Just in case you missed the link for some reason, here is it again:
You must have a radically different idea of "easy to read paper" than I have. ;-) Anyway, after multiple hours of staring at this paper and watching intricate type signatures swim before my eyes, I simply ended up being highly confused. (I especially like the way that what's described in the paper doesn't quite match what's in the actual Haskell standard libraries...) After many hours of thinking about this, I eventually began to vaguely comprehend what it's saying. (I suspect the problem is that, rather like monads, the concepts it's attempting to explain are just so extremely abstract that it's hard to develop an intuitive notion about them.) So... something that's "applicative" is sort-of like a monad, but where the next action cannot vary depending on the result of some prior action? Is that about the size of it? (If so, why didn't you just *say* so?) But on the other hand, that would seem to imply that every monad is trivially applicative, yet studying the libraries this is not the case. Indeed several of the libraries seem to go out of their way to implement duplicate functionallity for monad and applicative. (Hence the sea of identical and nearly identical type sigantures for functions with totally different names that had me confused for so long.) If you think in terms of containers, then "c x" is a container of "x values". Then, the type signature sequence :: c1 (c2 x) -> c2 (c1 x) kind-of makes sense. (Obviously the two containers are constrained to particular classes.) So that's "traversable", is it? Again, we have "sequence" and "sequenceA", indicating that monads and applicatives aren't actually the same somehow. Also, before you can put anything into Traversable, it has to be in Functor (no hardship there) and Foldable. Foldable seems simplish, except that it refers to some odd "monoid" class that looks suspiciously like "MonadPlus" but isn't... wuh? OK, maybe I should just stop attempting to comprehend this stuff and write the code... At this point learning about applicative and traversable isn't actually solving my problem.

Andrew Coppin wrote:
But on the other hand, that would seem to imply that every monad is trivially applicative, yet studying the libraries this is not the case. Indeed several of the libraries seem to go out of their way to implement duplicate functionallity for monad and applicative. (Hence the sea of identical and nearly identical type sigantures for functions with totally different names that had me confused for so long.) Actually, it is the case. It is technically possible to write:
instance Monad m => Applicative m where pure = return (<*>) = ap We don't include the above definition because it elimimates all possibility of specialization. The reason for the separation of the two for many functions is so that types which are instances of only one of the two can still take advantage of the functionality.
Foldable seems simplish, except that it refers to some odd "monoid" class that looks suspiciously like "MonadPlus" but isn't... wuh? A Monoid is simply anything that has an identity element (mempty) and an associative binary operation (mappend). It is not necessary for a complete instance of Foldable.
- Jake

Jake McArthur wrote:
Andrew Coppin wrote:
But on the other hand, that would seem to imply that every monad is trivially applicative, yet studying the libraries this is not the case. Actually, it is the case. It is technically possible to write:
instance Monad m => Applicative m where pure = return (<*>) = ap
We don't include the above definition because it elimimates all possibility of specialization.
I don't follow.
The reason for the separation of the two for many functions is so that types which are instances of only one of the two can still take advantage of the functionality.
Well, that makes sense once you assume two seperate, unconnected classes. I'm still fuzzy on that first point though.
Foldable seems simplish, except that it refers to some odd "monoid" class that looks suspiciously like "MonadPlus" but isn't... wuh? A Monoid is simply anything that has an identity element (mempty) and an associative binary operation (mappend). It is not necessary for a complete instance of Foldable.
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?

On Fri, Oct 3, 2008 at 3:10 PM, Andrew Coppin
Jake McArthur wrote:
Andrew Coppin wrote:
But on the other hand, that would seem to imply that every monad is trivially applicative, yet studying the libraries this is not the case.
Actually, it is the case. It is technically possible to write:
instance Monad m => Applicative m where pure = return (<*>) = ap
We don't include the above definition because it elimimates all possibility of specialization.
I don't follow.
For some monads, there are implementations of <*> which are more efficient than the one provided by ap. Similarly, there are ways to implement fmap which are more efficient than using liftM. Of course, the *real* reason we don't define the instance given above is that there are instances of Applicative that aren't monads, and we want to avoid overlapping instances.
The reason for the separation of the two for many functions is so that types which are instances of only one of the two can still take advantage of the functionality.
Well, that makes sense once you assume two seperate, unconnected classes. I'm still fuzzy on that first point though.
It's historical. Monad pre-dates Applicative by several years. Because it's part of the Haskell 98 standard, no one is willing to change Monad to make Applicative a superclass. Thus all the duplication. (Also, many of the duplicate functions are found in the Haskell 98 report, so we can't replace them with their more-general Applicative variants.)
Foldable seems simplish, except that it refers to some odd "monoid" class that looks suspiciously like "MonadPlus" but isn't... wuh?
A Monoid is simply anything that has an identity element (mempty) and an associative binary operation (mappend). It is not necessary for a complete instance of Foldable.
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?
There are at least three reasons why MonadPlus and Monoid are distinct.
First, MonadPlus is older than Monoid, even though Monoid is more general.
Second, MonadPlus and Monoid have different kinds, * -> * and *,
respectively. Instances of MonadPlus are more restricted, because they
have to work with any type parameter, whereas instances of Monoid can
place constraints.
Third, instances of MonadPlus must follow additional laws relating the
behavior of mplus and mzero to return and (>>=).
--
Dave Menendez

David Menendez wrote:
For some monads, there are implementations of <*> which are more efficient than the one provided by ap. Similarly, there are ways to implement fmap which are more efficient than using liftM.
Of course, the *real* reason we don't define the instance given above is that there are instances of Applicative that aren't monads, and we want to avoid overlapping instances.
OK, now I understand. (Of course, if Applicative was already a superclass of Monad, presumably that last wouldn't still stand?)
Well, that makes sense once you assume two seperate, unconnected classes. I'm still fuzzy on that first point though.
It's historical.
Ah. So "brokenness in the name of backwards compatibility"? (Is this why we have "alternate Prelude modules"?)
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?
There are at least three reasons why MonadPlus and Monoid are distinct.
First, MonadPlus is older than Monoid, even though Monoid is more general.
Second, MonadPlus and Monoid have different kinds, * -> * and *, respectively. Instances of MonadPlus are more restricted, because they have to work with any type parameter, whereas instances of Monoid can place constraints.
Third, instances of MonadPlus must follow additional laws relating the behavior of mplus and mzero to return and (>>=).
OK, good. Also, I notice that the documentation for Monoid mentions that numbers form one. But that's not actually correct. Numbers for *several*! And yet, a given number type can only have *one* Monoid instance. (Or indeed, only one instance for _any_ typeclass.) How do you get round that?

On Fri, Oct 3, 2008 at 12:10 PM, Andrew Coppin
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?
MonadPlus is a class for type constructors, generic over the type of the elements: class MonadPlus m where mzero :: m a mplus :: m a -> m a -> m a (note the lack of "a" in the class signature; the methods have to be defined for ALL possible "a"). whereas monoid is a class for concrete types: class Monoid a where mempty :: a mappend :: a -> a -> a The MonadPlus instance for lists is very constrained: instance MonadPlus [] where mzero = [] -- only possibly definition mplus = (++) There's no other possible fully-defined definition of mzero, and the laws for mplus constrain its definition significantly; the only real change you are allowed to make is to merge the elements of the two input lists in some interesting fashion. Even then you need to keep the relative ordering of the elements within a list the same. The monoid definition is far more open, however; there are many possible monoid definitions for lists. This admits a definition like the following: instance Monoid a => Monoid [a] where mempty = [mempty] mappend xs ys = [x `mappend` y | x <- xs, y <- ys] Of course, other definitions are possible; this one fits the monoid laws: mempty `mappend` a == a a `mappend` mempty == a but there are other choices that do so as well (one based on zipWith, for example, , or drop the "Monoid a" constraint and just use [] and ++) It's similar to Monad vs. Applicative; you can use any Monad definition to create a valid Applicative definition, but it's possible that other definitions exist, or, at the least, are more efficient. -- ryan

On Oct 3, 2008, at 15:10 , Andrew Coppin wrote:
The reason for the separation of the two for many functions is so that types which are instances of only one of the two can still take advantage of the functionality.
Well, that makes sense once you assume two seperate, unconnected classes. I'm still fuzzy on that first point though.
Foldable seems simplish, except that it refers to some odd "monoid" class that looks suspiciously like "MonadPlus" but isn't... wuh? A Monoid is simply anything that has an identity element (mempty) and an associative binary operation (mappend). It is not necessary for a complete instance of Foldable.
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?
Because typeclasses aren't like OO classes. Specifically: while you can specify what looks like class inheritance (e.g. "this Monad is also a Monoid" you can't override inherited methods (because it's a Monad, you can't specify as part of the Monad instance the definition of a Monoid class function). So if you want to define MonadPlus to look like a Monad and a Monoid, you have to pick one and *duplicate* the other (without using the same names, since they're already taken by the typeclass you *don't* choose). Usually this isn't a problem, because experienced Haskell programmers don't try to use typeclasses for OO. But there are the occasional mathematically-inspired relationships (Functor vs. Monad, MonadPlus vs. Monoid, Applicative vs. Monad, etc.) that can't be expressed "properly" as a result. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Oct 3, 2008, at 15:10 , Andrew Coppin wrote:
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?
Because typeclasses aren't like OO classes. Specifically: while you can specify what looks like class inheritance (e.g. "this Monad is also a Monoid" you can't override inherited methods (because it's a Monad, you can't specify as part of the Monad instance the definition of a Monoid class function). So if you want to define MonadPlus to look like a Monad and a Monoid, you have to pick one and *duplicate* the other (without using the same names, since they're already taken by the typeclass you *don't* choose).
I was thinking more, why not just delete MonadPlus completely, and have any function that needs a monad that's also a monoid say so in its context? (Obviously one of the answers to that is "because it would break vast amounts of existing code".)

Andrew Coppin wrote:
I was thinking more, why not just delete MonadPlus completely, and have any function that needs a monad that's also a monoid say so in its context? (Obviously one of the answers to that is "because it would break vast amounts of existing code".) Because they are not the same. MonadPlus has more restrictions than Monoid. For an instance of the form "instance MonadPlus m where", m a _must_ be a Monoid for _all_ a, whereas "instance Monoid (m a) where" may be defined for some specific a instead.
- Jake

Jake McArthur wrote:
Andrew Coppin wrote:
I was thinking more, why not just delete MonadPlus completely, and have any function that needs a monad that's also a monoid say so in its context? (Obviously one of the answers to that is "because it would break vast amounts of existing code".) Because they are not the same. MonadPlus has more restrictions than Monoid. For an instance of the form "instance MonadPlus m where", m a _must_ be a Monoid for _all_ a, whereas "instance Monoid (m a) where" may be defined for some specific a instead.
OK, fair enough then.

On Fri, 2008-10-03 at 21:12 +0100, Andrew Coppin wrote:
Brandon S. Allbery KF8NH wrote:
On Oct 3, 2008, at 15:10 , Andrew Coppin wrote:
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?
Because typeclasses aren't like OO classes. Specifically: while you can specify what looks like class inheritance (e.g. "this Monad is also a Monoid" you can't override inherited methods (because it's a Monad, you can't specify as part of the Monad instance the definition of a Monoid class function). So if you want to define MonadPlus to look like a Monad and a Monoid, you have to pick one and *duplicate* the other (without using the same names, since they're already taken by the typeclass you *don't* choose).
I was thinking more, why not just delete MonadPlus completely, and have any function that needs a monad that's also a monoid say so in its context?
This would be clunky. Consider: select as = msum $ do (as0, a:as) <- breaks as return $ do x <- a return (x, as0 ++ as) -- | Divide a list into (snoc-list, cons-list) pairs every possible -- way breaks :: [a] -> [([a], [a])] breaks as = breaks [] as where breaks' as0 [] = [(as0, [])] breaks' as0 (a:as) = (as0, a:as) : breaks' (a:as0) as You can say select :: MonadPlus m => [m a] -> m (a, [m a]) but not select :: (Monad m, Monoid (m a)) => [m a] -> m (a, [m a]) --- for this particular implementation, you need select :: (Monad m, Monoid (m (a, [m a]))) => [m a] -> m (a, [m a]) but then if you want to write select_ = fmap fst . select you have select_ :: (Monad m, Monoid (m (a, [m a]))) => [m a] -> m a . This is a wtf constraint, obviously. You can avoid this by writing select_ :: (Monad m, forall b. Monoid (m b)) => [m a] -> m a but that's somewhat beyond the scope of the existing type class system. Unless you write a new type class that is *explicitly* (Monad m, forall b. Monoid (m b)). Which is what MonadPlus is. jcc

On 2008 Oct 3, at 16:12, Andrew Coppin wrote:
Brandon S. Allbery KF8NH wrote:
On Oct 3, 2008, at 15:10 , Andrew Coppin wrote:
Again, it looks like MonadPlus == Monad + Monoid, except all the method names are different. Why do we have this confusing duplication?
Because typeclasses aren't like OO classes. Specifically: while you can specify what looks like class inheritance (e.g. "this Monad is also a Monoid" you can't override inherited methods (because it's a Monad, you can't specify as part of the Monad instance the definition of a Monoid class function). So if you want to define MonadPlus to look like a Monad and a Monoid, you have to pick one and *duplicate* the other (without using the same names, since they're already taken by the typeclass you *don't* choose).
I was thinking more, why not just delete MonadPlus completely, and have any function that needs a monad that's also a monoid say so in its context? (Obviously one of the answers to that is "because it would break vast amounts of existing code".)
It also touches on some Haskell98 braindamage. (Look up "MonadZero".) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Thu, Oct 2, 2008 at 3:40 PM, Andrew Coppin
David Menendez wrote:
You could try using an exception monad transformer here
I thought I already was?
No, a monad transformer is a type constructor that takes a monad as an argument and produces another monad. So, (ErrorT ErrorType) is a monad transformer, and (ErrorT ErrorType m) is a monad, for any monad m. If it helps, a monad will always have kind * -> *, so a monad transformer will have kind (* -> *) -> (* -> *). When people talk about stacking monads, they're almost always talking about composing monad transformers, e.g. ReaderT Env (ErrorT ErrorType (StateT State IO)) :: * -> * is a monad built by successively applying three monad transformers to IO. If you look at the type you were using, you see that it breaks down into (Either ErrorType) (ResultSet State), where Either ErrorType :: * -> * and ResultSet State :: *. Thus, the monad is Either ErrorType. The fact that ResultSet is also a monad isn't enough to give you an equivalent to (>>=), without one of the functions below. inner :: ResultSet (Either ErrorType (ResultSet alpha)) -> Either ErrorType (ResultSet alpha) outer :: Either ErrorType (ResultSet (Either ErrorType alpha)) -> Either ErrorType (ResultSet alpha) swap :: ResultSet (Either ErrorType alpha) -> Either ErrorType (ResultSet alpha)
If you must have something equivalent to Either ErrorType (ResultSet a), you either need to (1) redesign ResultSet to include error handling, (2) redesign ResultSet to be a monad transformer, or (3) restrict yourself to the operations in Applicative.
Option (3) works because applicative functors *do* compose. (Also, every instance of Monad is trivially an instance of Applicative.)
Uh... what's Applicative? (I had a look at Control.Applicative, but it just tells me that it's "a strong lax monoidal functor". Which isn't very helpful, obviously.)
Applicative is a class of functors that are between Functor and Monad in terms of capabilities. Instead of (>>=), they have an operation (<*>) :: f (a -> b) -> f a -> f b, which generalizes Control.Monad.ap. The nice thing about Applicative functors is that they compose. If F and G are applicative functors, it's trivial to create a new applicative functor Comp F G. newtype Comp f g a = Comp { deComp :: f (g a) } instance (Functor f, Functor g) => Functor (Comp f g) where fmap f = Comp . fmap (fmap f) . deComp instance (Applicative f, Applicative g) => Applicative (Comp f g) where pure = Comp . pure . pure a <*> b = Comp $ liftA2 (<*>) (deComp a) (deComp b) With monads, you can't make (Comp m1 m2) a monad without a function analogous to inner, outer, or swap.
From your code examples, it isn't clear to me that applicative functors are powerful enough, but I can't really say without knowing what you're trying to do. The fact that the functions you gave take a state as an argument and return a state suggests that things could be refactored further.
--
Dave Menendez

David Menendez wrote:
On Thu, Oct 2, 2008 at 3:40 PM, Andrew Coppin
wrote: David Menendez wrote:
You could try using an exception monad transformer here
I thought I already was?
No, a monad transformer is a type constructor that takes a monad as an argument and produces another monad. So, (ErrorT ErrorType) is a monad transformer, and (ErrorT ErrorType m) is a monad, for any monad m.
Right, OK.
If you look at the type you were using, you see that it breaks down into (Either ErrorType) (ResultSet State), where Either ErrorType :: * -> * and ResultSet State :: *. Thus, the monad is Either ErrorType. The fact that ResultSet is also a monad isn't enough to give you an equivalent to (>>=), without one of the functions below.
OK, that makes sense.
Uh... what's Applicative? (I had a look at Control.Applicative, but it just tells me that it's "a strong lax monoidal functor". Which isn't very helpful, obviously.)
Applicative is a class of functors that are between Functor and Monad in terms of capabilities. Instead of (>>=), they have an operation (<*>) :: f (a -> b) -> f a -> f b, which generalizes Control.Monad.ap.
(As an aside, Control.Monad.ap is not a function I've ever heard of. It seems simple enough, but what an unfortunate name...!)
The nice thing about Applicative functors is that they compose.
With monads, you can't make (Comp m1 m2) a monad without a function analogous to inner, outer, or swap.
So I see. I'm still not convinced that Applicative helps me in any way though...
From your code examples, it isn't clear to me that applicative functors are powerful enough, but I can't really say without knowing what you're trying to do.
The whole list-style "multiple inputs/multiple outputs" trip, basically.
The fact that the functions you gave take a state as an argument and return a state suggests that things could be refactored further.
If you look at run_or, you'll see that this is _not_ a simple state monad, as in that function I run two actions starting from _the same_ initial state - something which, AFAIK, is impossible (or at least very awkward) with a state monad. Really, it's a function that takes a state and generates a new state, but it may also happen to generate *multiple* new states. It also consumes a Foo or two in the process.

Andrew Coppin wrote:
(As an aside, Control.Monad.ap is not a function I've ever heard of. It seems simple enough, but what an unfortunate name...!) I think it makes sense. It stands for "apply," or at least that is what I think of when I see it. If we have a function f :: A -> B -> C -> D and values a :: m A, b :: m B, c :: m C, then we can do:
f `liftM` a `ap` b `ap` c ... which is the same as (using Applicative): f <$> a <*> b <*> c ... both having type m D. - Jake

Jake McArthur wrote:
Andrew Coppin wrote:
(As an aside, Control.Monad.ap is not a function I've ever heard of. It seems simple enough, but what an unfortunate name...!) I think it makes sense. It stands for "apply," or at least that is what I think of when I see it.
There can be little doubt that this is what the designers intended. However, why didn't they name it, say, "apply"? I just think that Haskell already has too many names like "id" and "nub" and "elem" and "Eq" and "Ix". Would it kill anybody to write out more descriptive names? Also, I'm fuzzy on why ap is even a useful function to have in the first place. I can see what it does, but when are you ever going to need a function like that? (I'm not saying we should get rid of it, I'm just puzzled as to why anybody thought to include it to start with.)
If we have a function f :: A -> B -> C -> D and values a :: m A, b :: m B, c :: m C, then we can do:
f `liftM` a `ap` b `ap` c
... which is the same as (using Applicative):
f <$> a <*> b <*> c
... both having type m D.
Again we seem to have two different sets of functions which none the less appear to do exactly the same thing.

On Fri, Oct 3, 2008 at 1:39 PM, Andrew Coppin
David Menendez wrote:
Applicative is a class of functors that are between Functor and Monad in terms of capabilities. Instead of (>>=), they have an operation (<*>) :: f (a -> b) -> f a -> f b, which generalizes Control.Monad.ap.
(As an aside, Control.Monad.ap is not a function I've ever heard of. It seems simple enough, but what an unfortunate name...!)
I believe it's short for "apply". "ap" generalizes the liftM* functions, so liftM2 f a b = return f `ap` a `ap` b liftM3 f a b c = return f `ap` a `ap` b `ap` c and so forth. It wasn't until fairly recently that people realized that you could do useful things if you had "return" and "ap", but not (>>=), which why we have some unfortunate limitations in the Haskell prelude, like Applicative not being a superclass of Monad. This leads to all the duplication between Applicative and Monad. In a perfect world, we would only need the Applicative versions.
The nice thing about Applicative functors is that they compose.
With monads, you can't make (Comp m1 m2) a monad without a function analogous to inner, outer, or swap.
So I see. I'm still not convinced that Applicative helps me in any way though...
To be honest, neither am I. But it's a useful thing to be aware of.
From your code examples, it isn't clear to me that applicative functors are powerful enough, but I can't really say without knowing what you're trying to do.
The whole list-style "multiple inputs/multiple outputs" trip, basically.
Would you be willing to share the implementation of ResultSet? If you're relying on a list somewhere, then it should be possible to switch the implementation to one of the nondeterminism monad transformers, which would give you the exception behavior you want.
The fact that the functions you gave take a state as an argument and return a state suggests that things could be refactored further.
If you look at run_or, you'll see that this is _not_ a simple state monad, as in that function I run two actions starting from _the same_ initial state - something which, AFAIK, is impossible (or at least very awkward) with a state monad.
Really, it's a function that takes a state and generates a new state, but it may also happen to generate *multiple* new states. It also consumes a Foo or two in the process.
That's what happens if you apply a state monad transformer to a
nondeterminism monad.
plusMinusOne :: StateT Int [] ()
plusMinusOne = get s >>= \s -> mplus (put $ s + 1) (put $ s - 1)
execStateT plusMinusOne 0 == [1,-1]
execStateT (plusMinusOne >> plusMinusOne) 0 == [2,0,0,-2]
(FYI, execStateT is similar to runStateT, except that it discards the
return value, which is () in our example.)
So it might be possible to rewrite your code along these lines:
type M = StateT State []
run :: Foo -> M ()
runOr :: Foo -> Foo -> M ()
runOr x y = mplus (run x) (run y)
runAnd :: Foo -> Foo -> M ()
runAnd x y = run x >> run y
The type "StateT State [] alpha" is isomorphic to "State -> [(alpha,
State)]", which means that each of the computations in mplus gets its
own copy of the state.
There are a few ways to add exceptions to this, depending on how you
want the exceptions to interact with the non-determinism.
1. StateT State (ErrorT ErrorType []) alpha
This corresponds to "State -> [(Either ErrorType alpha, State)]".
Each branch maintains its own state and is isolated from exceptions in
other branches.
In other words,
catchErr (mplus a b) h == mplus (catchErr a h) (catchErr b h)
2. StateT State (NondetT (Either ErrorType)) alpha
(NondetT isn't in the standard libraries, but I can provide code if needed.)
This corresponds to "State -> Either ErrorType [(alpha, State)]".
Left uncaught, an exception raised in any branch will cause all
branches to fail.
mplus (throw e) a == throw e
--
Dave Menendez

David Menendez wrote:
On Fri, Oct 3, 2008 at 1:39 PM, Andrew Coppin
wrote: (As an aside, Control.Monad.ap is not a function I've ever heard of. It seems simple enough, but what an unfortunate name...!)
I believe it's short for "apply".
Yeah, but shame about the name. ;-)
"ap" generalizes the liftM* functions, so
liftM2 f a b = return f `ap` a `ap` b liftM3 f a b c = return f `ap` a `ap` b `ap` c
and so forth.
Now that at least makes sense. (It's non-obvious that you can use it for this. If it weren't for curried functions, this wouldn't work at all...)
It wasn't until fairly recently that people realized that you could do useful things if you had "return" and "ap", but not (>>=), which why we have some unfortunate limitations in the Haskell prelude, like Applicative not being a superclass of Monad.
This leads to all the duplication between Applicative and Monad. In a perfect world, we would only need the Applicative versions.
OK. So it's broken "for compatibility" then? (Presumably any time you change something from the Prelude, mass breakage ensues!)
So I see. I'm still not convinced that Applicative helps me in any way though...
To be honest, neither am I. But it's a useful thing to be aware of.
OK. (Now that I've figured out what it *is*...)
Would you be willing to share the implementation of ResultSet? If you're relying on a list somewhere, then it should be possible to switch the implementation to one of the nondeterminism monad transformers, which would give you the exception behavior you want.
Consider the following: factorise n = do x <- [1..] y <- [1..] if x*y == n then return (x,y) else fail "not factors" This is a very stupid way to factorise an integer. (But it's also very general...) As you may already be aware, this fails miserably because it tries all possible values for y before trying even one new value for x. And since both lists there are infinite, this causes an endless loop that produces (almost) nothing. My ResultSet monad works the same way as a list, except that the above function discovers all finite solutions in finite time. The result is still infinite, but all the finite solutions are within a finite distance of the beginning. Achieving this was Seriously Non-Trivial. (!) As in, it's several pages of seriously freaky code that took me days to develop. AFAIK, nothing like this already exists in the standard libraries.
If you look at run_or, you'll see that this is _not_ a simple state monad, as in that function I run two actions starting from _the same_ initial state - something which, AFAIK, is impossible (or at least very awkward) with a state monad.
Really, it's a function that takes a state and generates a new state, but it may also happen to generate *multiple* new states. It also consumes a Foo or two in the process.
That's what happens if you apply a state monad transformer to a nondeterminism monad.
So it might be possible to rewrite your code along these lines:
type M = StateT State []
run :: Foo -> M ()
runOr :: Foo -> Foo -> M () runOr x y = mplus (run x) (run y)
runAnd :: Foo -> Foo -> M () runAnd x y = run x >> run y
The type "StateT State [] alpha" is isomorphic to "State -> [(alpha, State)]", which means that each of the computations in mplus gets its own copy of the state.
What does mplus do in this case? (I know what it does for Maybe, but not for any other monad.)
There are a few ways to add exceptions to this, depending on how you want the exceptions to interact with the non-determinism.
1. StateT State (ErrorT ErrorType []) alpha
Each branch maintains its own state and is isolated from exceptions in other branches.
Nope, that's wrong. In this program, Foo is provided by the user, and an "exception" indicates that user entered an invalid expression. Thus all processing should immediately abort and a message should be reported to the wetware for rectification. (That also means that there will never be any need to "catch" exceptions, since they are all inherantly fatal.)
2. StateT State (NondetT (Either ErrorType)) alpha
(NondetT isn't in the standard libraries, but I can provide code if needed.)
Left uncaught, an exception raised in any branch will cause all branches to fail.
That looks more like it, yes.

On Fri, Oct 3, 2008 at 12:43 PM, Andrew Coppin
factorise n = do x <- [1..] y <- [1..] if x*y == n then return (x,y) else fail "not factors"
This is a very stupid way to factorise an integer. (But it's also very general...) As you may already be aware, this fails miserably because it tries all possible values for y before trying even one new value for x. And since both lists there are infinite, this causes an endless loop that produces (almost) nothing.
You should look at LogicT at http://okmij.org/ftp/Computation/monads.html The magic words you are looking for are "fair disjunction" and "fair conjunction". The paper is full of mind-stretching code but it already does everything you want. And it is a monad transformer already, so it's easy to attach Error to it. -- ryan

On Fri, 2008-10-03 at 20:43 +0100, Andrew Coppin wrote:
David Menendez wrote:
It wasn't until fairly recently that people realized that you could do useful things if you had "return" and "ap", but not (>>=), which why we have some unfortunate limitations in the Haskell prelude, like Applicative not being a superclass of Monad.
This leads to all the duplication between Applicative and Monad. In a perfect world, we would only need the Applicative versions.
OK. So it's broken "for compatibility" then? (Presumably any time you change something from the Prelude, mass breakage ensues!)
I'm not a big fan of backward-compatibility myself, but changing Monad to be a sub-class of Applicative actually would have broken every monad instance in existence (at the time Applicative was added, since it didn't have any instances yet). I don't know what proportion of Haskell programs/libraries/etc. have at least one Monad instance in them, but I would guess it's high. jcc

Jonathan Cast wrote:
On Fri, 2008-10-03 at 20:43 +0100, Andrew Coppin wrote:
OK. So it's broken "for compatibility" then? (Presumably any time you change something from the Prelude, mass breakage ensues!)
I'm not a big fan of backward-compatibility myself, but changing Monad to be a sub-class of Applicative actually would have broken every monad instance in existence (at the time Applicative was added, since it didn't have any instances yet). I don't know what proportion of Haskell programs/libraries/etc. have at least one Monad instance in them, but I would guess it's high.
Hmm, that's quite a lot of breakage. So if it had been set up this way from day 1, we wouldn't be having this conversation, but it's now too expensive to change it. Is that basically what it comes down to?

On Fri, 2008-10-03 at 21:02 +0100, Andrew Coppin wrote:
Jonathan Cast wrote:
On Fri, 2008-10-03 at 20:43 +0100, Andrew Coppin wrote:
OK. So it's broken "for compatibility" then? (Presumably any time you change something from the Prelude, mass breakage ensues!)
I'm not a big fan of backward-compatibility myself, but changing Monad to be a sub-class of Applicative actually would have broken every monad instance in existence (at the time Applicative was added, since it didn't have any instances yet). I don't know what proportion of Haskell programs/libraries/etc. have at least one Monad instance in them, but I would guess it's high.
Hmm, that's quite a lot of breakage.
So if it had been set up this way from day 1, we wouldn't be having this conversation, but it's now too expensive to change it. Is that basically what it comes down to?
Sort of. (Although I note that Monad isn't a sub-class of Functor, either, and I think those are coeval.) It is too expensive to change it during the period between when Applicative was discovered and now. But that could change in the future --- I'm sure a much higher of types with Monad instances happen to have Applicative instances as well now. If that proportion rises by enough, the backward compatibility argument would become less compelling. jcc

On Fri, 2008-10-03 at 12:59 -0700, Jonathan Cast wrote:
On Fri, 2008-10-03 at 21:02 +0100, Andrew Coppin wrote:
Jonathan Cast wrote:
On Fri, 2008-10-03 at 20:43 +0100, Andrew Coppin wrote:
OK. So it's broken "for compatibility" then? (Presumably any time you change something from the Prelude, mass breakage ensues!)
I'm not a big fan of backward-compatibility myself, but changing Monad to be a sub-class of Applicative actually would have broken every monad instance in existence (at the time Applicative was added, since it didn't have any instances yet). I don't know what proportion of Haskell programs/libraries/etc. have at least one Monad instance in them, but I would guess it's high.
Hmm, that's quite a lot of breakage.
So if it had been set up this way from day 1, we wouldn't be having this conversation, but it's now too expensive to change it. Is that basically what it comes down to?
Sort of. (Although I note that Monad isn't a sub-class of Functor, either, and I think those are coeval.) It is too expensive to change it during the period between when Applicative was discovered and now. But that could change in the future --- I'm sure a much higher of types with ^ proportion Monad instances happen to have Applicative instances as well now. If that proportion rises by enough, the backward compatibility argument would become less compelling.
jcc

On Fri, Oct 3, 2008 at 3:43 PM, Andrew Coppin
David Menendez wrote:
It wasn't until fairly recently that people realized that you could do useful things if you had "return" and "ap", but not (>>=), which why we have some unfortunate limitations in the Haskell prelude, like Applicative not being a superclass of Monad.
This leads to all the duplication between Applicative and Monad. In a perfect world, we would only need the Applicative versions.
OK. So it's broken "for compatibility" then? (Presumably any time you change something from the Prelude, mass breakage ensues!)
Exactly. Since the Prelude is specified in the Haskell 98 report, you can't add or subtract things without losing Haskell 98 compatibility. We *could* define a new Prelude that did things more sensibly, but then code either has to pick which Prelude to support or else jump through extra hoops to be cross-compatible.
Would you be willing to share the implementation of ResultSet? If you're relying on a list somewhere, then it should be possible to switch the implementation to one of the nondeterminism monad transformers, which would give you the exception behavior you want.
Consider the following:
factorise n = do x <- [1..] y <- [1..] if x*y == n then return (x,y) else fail "not factors"
This is a very stupid way to factorise an integer. (But it's also very general...) As you may already be aware, this fails miserably because it tries all possible values for y before trying even one new value for x. And since both lists there are infinite, this causes an endless loop that produces (almost) nothing.
My ResultSet monad works the same way as a list, except that the above function discovers all finite solutions in finite time. The result is still infinite, but all the finite solutions are within a finite distance of the beginning. Achieving this was Seriously Non-Trivial. (!) As in, it's several pages of seriously freaky code that took me days to develop.
AFAIK, nothing like this already exists in the standard libraries.
Now I'm even more curious to see how you did it. I spent some time a few months ago developing a monad that does breadth-first search. It would be able to handle the example you gave almost without change. Some other possibilities: (1) logict http://hackage.haskell.org/cgi-bin/hackage-scripts/package/logict This defines a backtracking monad transformer (the NondetT I mentioned in my previous message), and provides a "fair" variant of (>>=) that you could use to define factorise. It's not as foolproof as the other options. (2) control-monad-omega http://hackage.haskell.org/cgi-bin/hackage-scripts/package/control-monad-ome... This is a monad similar to [] that uses a "diagonal" search pattern. (3) Oleg Kiselyov's fair and backtracking monad http://okmij.org/ftp/Computation/monads.html#fair-bt-stream This uses a search pattern that I don't fully understand, and only satisfies the Monad and MonadPlus laws if you ignore the order of results, but think it's at least as robust as Omega.
If you look at run_or, you'll see that this is _not_ a simple state monad, as in that function I run two actions starting from _the same_ initial state - something which, AFAIK, is impossible (or at least very awkward) with a state monad.
Really, it's a function that takes a state and generates a new state, but it may also happen to generate *multiple* new states. It also consumes a Foo or two in the process.
That's what happens if you apply a state monad transformer to a nondeterminism monad.
So it might be possible to rewrite your code along these lines:
type M = StateT State []
run :: Foo -> M ()
runOr :: Foo -> Foo -> M () runOr x y = mplus (run x) (run y)
runAnd :: Foo -> Foo -> M () runAnd x y = run x >> run y
The type "StateT State [] alpha" is isomorphic to "State -> [(alpha, State)]", which means that each of the computations in mplus gets its own copy of the state.
What does mplus do in this case? (I know what it does for Maybe, but not for any other monad.)
"mplus a b" returns all the results returned by "a" and "b". For lists, it returns all the results of "a" before the results of "b". I suspect it corresponds to "merge" in your code. For true backtracking monads (that is, not Maybe), mplus also has this property: mplus a b >>= f == mplus (a >>= f) (b >>= f) There is a school of thought that Maybe (and Error/ErrorT) should not be instances of MonadPlus because they do not satisfy that law.
2. StateT State (NondetT (Either ErrorType)) alpha
(NondetT isn't in the standard libraries, but I can provide code if needed.)
Left uncaught, an exception raised in any branch will cause all branches to fail.
That looks more like it, yes.
That's what I figured. You'll need a transformer, then, which rules
out Omega. Since you don't care about catching exceptions, you can
just do something like
type M = StateT State (LogicT (Either ErrorType))
throwM :: ErrorType -> M a
throwM = lift . lift . Left
Or, if you want to try my breadth-first monad, I can send you a copy.
It supports exception handling out of the box.
--
Dave Menendez

Andrew Coppin wrote:
"ap" generalizes the liftM* functions, so
liftM2 f a b = return f `ap` a `ap` b liftM3 f a b c = return f `ap` a `ap` b `ap` c
and so forth.
Now that at least makes sense. (It's non-obvious that you can use it for this. If it weren't for curried functions, this wouldn't work at all...)
Note that the documentation for ap states:
In many situations, the liftM operations can be replaced by uses of ap, which promotes function application.
return f `ap` x1 `ap` ... `ap` xn
is equivalent to
liftMn f x1 x2 ... xn
Tillmann

David Menendez wrote:
So it might be possible to rewrite your code along these lines:
type M = StateT State []
run :: Foo -> M ()
runOr :: Foo -> Foo -> M () runOr x y = mplus (run x) (run y)
runAnd :: Foo -> Foo -> M () runAnd x y = run x >> run y
The type "StateT State [] alpha" is isomorphic to "State -> [(alpha, State)]", which means that each of the computations in mplus gets its own copy of the state.
There are a few ways to add exceptions to this, depending on how you want the exceptions to interact with the non-determinism.
2. StateT State (NondetT (Either ErrorType)) alpha
I have some longwinded code that works, but I'm still thinking about how to do this more elegantly. It looks like what I really need is something like type M = StateT State (ResultSetT (ErrorT ErrorType Identity)) Is that the correct ordering? If so, I guess that means I have to somehow construct ResultSetT. Is there an easy way to do that, given that I already have ResultSet? For example, if I put ResultSet into Traversable, would that let me do it?

Andrew Coppin wrote:
I have some longwinded code that works, but I'm still thinking about how to do this more elegantly. It looks like what I really need is something like
type M = StateT State (ResultSetT (ErrorT ErrorType Identity))
Is that the correct ordering?
If so, I guess that means I have to somehow construct ResultSetT. Is there an easy way to do that, given that I already have ResultSet? For example, if I put ResultSet into Traversable, would that let me do it?
...and again I'm talking to myself... :-/ So after much experimentation, I have managed to piece together the following facts: - It appears that the outer-most monad transformer represents the inner-most monad. So "StateT Foo ListT" means a list of stateful computations, while "ListT (StateT Foo)" means a stateful list of computations. - Each transformer seems to be defined as a newtype such that we have ListT :: m [x] -> ListT m x and runListT :: ListT m x -> m [x]. - By some magical process that I do not yet understand, I can wrap a StateT in 17 other transformers, and yet "get" and "put" do not require any lifting. (God only knows what happens if you were to use two StateTs in the same monad stack...) What I haven't figured out yet is how to turn ResultSet into ResultSetT. I seem to just spend most of my time being frustrated by the type checker. A useful trick is to say things like :t lift (undefined :: ListT Int) to figure out what type the various parts of a complex multi-monad expression have. (By now I'm seeing things like "return . return . return", which is just far out.) But sometimes I find myself desperately wanting to take some block of code and say "what type does *this* part of the expression have?" or "if I do x >>= y when y has *this* type, what type must x have?" It can be very hard to work this out mentally, and unfortunately there isn't any tool I'm aware of that will help you in this matter. After much testing, it appears that the utopian type definition at the very top of this message is in fact the thing I need. So if I can just figure out how to construct ResultSetT than I'm done. It looks like trying to build it from ResultSet is actually harder than just implementing it directly, so I'm going to try a direct transformer implementation instead. But it's seriously hard work! For reference, I humbly present ResultSet.hs: module Orphi.Kernel.ResultSet (ResultSet (), from_list, to_list, build, limit, cost, union) where data ResultSet x = Pack {unpack :: [[x]]} deriving (Eq) instance (Show x) => Show (ResultSet x) where show (Pack xss) = "from_list " ++ show xss instance Monad ResultSet where fail msg = Pack [] return x = Pack [[x]] (Pack xss) >>= f = Pack $ raw_bind xss (unpack . f) raw_bind :: [[x]] -> (x -> [[y]]) -> [[y]] raw_bind = work [] where work out [] _ = out work out (xs:xss) f = let yss = foldr raw_union out (map f xs) in if null yss then [] : work [] xss f else head yss : work (tail yss) xss f raw_union :: [[x]] -> [[x]] -> [[x]] raw_union [] yss = yss raw_union xss [] = xss raw_union (xs:xss) (ys:yss) = (xs ++ ys) : raw_union xss yss from_list :: [[x]] -> ResultSet x from_list = Pack to_list :: ResultSet x -> [[x]] to_list = unpack build :: [x] -> ResultSet x build = from_list . map return limit :: Int -> ResultSet x -> ResultSet x limit n (Pack xss) = Pack (take n xss) cost :: ResultSet x -> ResultSet x cost (Pack xss) = Pack ([]:xss) union :: ResultSet x -> ResultSet x -> ResultSet x union (Pack xss) (Pack yss) = Pack (raw_union xss yss)

Andrew Coppin wrote:
If so, I guess that means I have to somehow construct ResultSetT. Is there an easy way to do that, given that I already have ResultSet?
I haven't been following this thread closely, so forgive if this was already discussed, but my understanding is that the answer is no, in general. In the paper "Monad Transformers and Modular Interpreters"[*], Section 8 ("Lifting Operations") touches on some of the issues. That's from 1995 - I don't know if any progress on this has been made since then, other than that a standard set of the most common monad transformers is now available. Anton [*] http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.17.268

Hi Andrew, On Mon, Oct 06, 2008 at 09:48:51PM +0100, Andrew Coppin wrote:
data ResultSet x = Pack {unpack :: [[x]]} deriving (Eq)
Your ResultSet monad is roughly equivalent to newtype Nat = Nat Int instance Monoid Nat where mempty = Nat 0 (Nat x) `mappend` (Nat y) = Nat (x+y) type ResultSet' = WriterT Nat [] -- ResultSet' x = [(x, Nat)] where unpack :: ResultSet' x -> [[x]] gives a list whose nth element is the list of alternatives whose "cost" (Nat data) is n (with trailing [] lists removed). Except that using [[x]] internally lets you be lazy about handling items of high cost. (This is kind of neat actually.) I'd therefore guess that if there is an associated monad transformer ResultSetT, it's similarly equivalent to ResultSetT' m x = WriterT Nat (ListT m x) where ListT is some version of "ListT done right". But on the other hand, as I understand "ListT done right", you can think of ListT m x as a "list" of xs where you have to perform an action in the m monad to get each successive value in the list. The equivalence converting ResultSet' to ResultSet sort of "tears up" the list in a way I'm not sure is compatible with inserting a monad like that. Once again, all this high-falutin' nonsense corresponds to really concrete questions about what you want your code to *actually do*. Consider your original problem
run :: State -> Foo -> Either ErrorType (ResultSet State)
run_and :: State -> Foo -> Foo -> Either ErrorType (ResultSet State) {- some Either-ified version of run_and :: State -> Foo -> Foo -> ResultSet State run_and s0 x y = do s1 <- run s0 x s2 <- run s1 y return s2 -}
Say run s0 x returns many different possibilities s1 (with varying costs). And suppose run s1 y is a (Left err) for some of these s1 and a (Right whatever) for others. When should the overall result of run_and be a Left and when should it be a Right? And *which error* should you return if there's more than one Left? Do you really want to check whether every run s1 y is a (Right whatever)? In that case you are not gaining much from the laziness of ResultSet and might as well use ResultSet'. Until you decide the answer to questions of this kind, you can't know how to best structure your code. Regards, Reid Barton

The good news: I managed to turn ResultSet into a monad transformer. Yay, me! The bad news: It generates the entire result set before returning anything to the caller. In other words, it works perfectly for finite result sets, and locks up forever on infinite result sets. Since the entire *point* of the monad is to handle infinite result sets correctly, that's kind-of a problem. And one that I see absolutely no way of fixing. :-( Basically, the core code is something like raw_bind :: (Monad m) => [[x]] -> (x -> m (ResultSet y)) -> m (ResultSet y) raw_bind [] f = return empty raw_bind (xs:xss) f = do rsYs <- mapM f xs rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs) As you can see, this generates all of rsZ before attempting to return anything to the caller. And I'm really struggling to see any way to avoid that.

Am Dienstag, 7. Oktober 2008 20:27 schrieb Andrew Coppin:
The good news: I managed to turn ResultSet into a monad transformer. Yay, me!
The bad news: It generates the entire result set before returning anything to the caller.
In other words, it works perfectly for finite result sets, and locks up forever on infinite result sets. Since the entire *point* of the monad is to handle infinite result sets correctly, that's kind-of a problem. And one that I see absolutely no way of fixing. :-(
Basically, the core code is something like
raw_bind :: (Monad m) => [[x]] -> (x -> m (ResultSet y)) -> m (ResultSet y) raw_bind [] f = return empty raw_bind (xs:xss) f = do rsYs <- mapM f xs rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs)
As you can see, this generates all of rsZ before attempting to return anything to the caller. And I'm really struggling to see any way to avoid that.
Maybe it is as simple as raw_bind (xs:xss) f = do rsYs <- mapM f xs ~rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs) then rsZ should only be evaluated when it's needed

Daniel Fischer wrote:
Am Dienstag, 7. Oktober 2008 20:27 schrieb Andrew Coppin:
Basically, the core code is something like
raw_bind :: (Monad m) => [[x]] -> (x -> m (ResultSet y)) -> m (ResultSet y) raw_bind [] f = return empty raw_bind (xs:xss) f = do rsYs <- mapM f xs rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs)
As you can see, this generates all of rsZ before attempting to return anything to the caller. And I'm really struggling to see any way to avoid that.
Maybe it is as simple as
raw_bind (xs:xss) f = do rsYs <- mapM f xs ~rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs)
then rsZ should only be evaluated when it's needed
Ooo... "lazy pattern matching"? Can somebody explain to me, _very slowy_, exactly what that means? If I'm doing this right, it seems that rsZ <- raw_bind xss f ... desugards to raw_bind xss f >>= \rsZ -> ... If I'm not mistaken, the rsZ variable shouldn't be evaluated until needed *anyway*, so what is lazy pattern matching buying me here? Also, suppose I stack ResultSetT on top of IO. In that case, "f" is allowed to perform externally-visible I/O operations. If there really *is* a way to delay the execution of certain calls until the data is needed... well that doesn't look right somehow. In fact, it looks like what I'm trying to do *should* be impossible. :-/ Oh dear...

Am Dienstag, 7. Oktober 2008 22:09 schrieb Andrew Coppin:
Daniel Fischer wrote:
Am Dienstag, 7. Oktober 2008 20:27 schrieb Andrew Coppin:
Basically, the core code is something like
raw_bind :: (Monad m) => [[x]] -> (x -> m (ResultSet y)) -> m (ResultSet y) raw_bind [] f = return empty raw_bind (xs:xss) f = do rsYs <- mapM f xs rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs)
As you can see, this generates all of rsZ before attempting to return anything to the caller. And I'm really struggling to see any way to avoid that.
Maybe it is as simple as
raw_bind (xs:xss) f = do rsYs <- mapM f xs ~rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs)
then rsZ should only be evaluated when it's needed
Ooo... "lazy pattern matching"? Can somebody explain to me, _very slowy_, exactly what that means?
If I'm doing this right, it seems that
rsZ <- raw_bind xss f ...
desugards to
raw_bind xss f >>= \rsZ -> ...
If I'm not mistaken, the rsZ variable shouldn't be evaluated until needed *anyway*, so what is lazy pattern matching buying me here?
That depends on how your Monad (and union) is implemented, it may or may not make a difference. I must admit that I didn't really look at the code you posted, so I don't know what would be the case here. It was just an easy thing to try which *might* help. I will take a look, can't guarantee any result.
Also, suppose I stack ResultSetT on top of IO. In that case, "f" is allowed to perform externally-visible I/O operations. If there really *is* a way to delay the execution of certain calls until the data is needed... well that doesn't look right somehow. In fact, it looks like what I'm trying to do *should* be impossible. :-/ Oh dear...
To delay computations in IO until needed, you can use unsafeInterleaveIO: uiSeq :: [IO Int] -> IO [Int] uiSeq [] = do putStrLn "End of list" return [] uiSeq (a:as) = do x <- a putStrLn $ "got the value " ++ show x xs <- unsafeInterleaveIO $ uiSeq as return (x:xs) verbRet :: Int -> IO Int verbRet k = do putStrLn $ "Returning " ++ show k return k *Main> fmap (take 3) $ uiSeq [verbRet k | k <- [1 .. 10]] Returning 1 got the value 1 [1Returning 2 got the value 2 ,2Returning 3 got the value 3 ,3] *Main> fmap (take 3) $ sequence [verbRet k | k <- [1 .. 10]] Returning 1 Returning 2 Returning 3 Returning 4 Returning 5 Returning 6 Returning 7 Returning 8 Returning 9 Returning 10 [1,2,3] But unsafeInterleaveIO doesn't have its first six letters without a reason, so be careful when you want to use it (in general, don't). And of course you can't use it in generic monad transformer code, you might however be able to use class Monad m => LazyMonad m where lazyBind :: m a -> (a -> m b) -> m b lazySequence :: [m a] -> m [a] instance LazyMonad IO where lazyBind ma f = do a <- unsafeInterleaveIO ma f a lazySequence [] = return [] lazySequence (a:as) = do x <- a xs <- unsafeInterleaveIO $ lazySequence as return (x:xs)

On Tue, Oct 7, 2008 at 5:07 PM, Daniel Fischer
Am Dienstag, 7. Oktober 2008 22:09 schrieb Andrew Coppin:
Daniel Fischer wrote:
Maybe it is as simple as
raw_bind (xs:xss) f = do rsYs <- mapM f xs ~rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs)
then rsZ should only be evaluated when it's needed
Ooo... "lazy pattern matching"? Can somebody explain to me, _very slowy_, exactly what that means? <snip> If I'm not mistaken, the rsZ variable shouldn't be evaluated until needed *anyway*, so what is lazy pattern matching buying me here?
That depends on how your Monad (and union) is implemented, it may or may not make a difference. I must admit that I didn't really look at the code you posted, so I don't know what would be the case here. It was just an easy thing to try which *might* help.
Unless you're pattern matching against a constructor, which rsZ is
not, I think lazy pattern matching is no different from regular
pattern matching.
--
Dave Menendez

Am Dienstag, 7. Oktober 2008 23:38 schrieb David Menendez:
On Tue, Oct 7, 2008 at 5:07 PM, Daniel Fischer
wrote: Am Dienstag, 7. Oktober 2008 22:09 schrieb Andrew Coppin:
Daniel Fischer wrote:
Maybe it is as simple as
raw_bind (xs:xss) f = do rsYs <- mapM f xs ~rsZ <- raw_bind xss f return (foldr union (cost rsZ) rsYs)
then rsZ should only be evaluated when it's needed
Ooo... "lazy pattern matching"? Can somebody explain to me, _very slowy_, exactly what that means?
<snip>
If I'm not mistaken, the rsZ variable shouldn't be evaluated until needed *anyway*, so what is lazy pattern matching buying me here?
That depends on how your Monad (and union) is implemented, it may or may not make a difference. I must admit that I didn't really look at the code you posted, so I don't know what would be the case here. It was just an easy thing to try which *might* help.
Unless you're pattern matching against a constructor, which rsZ is not, I think lazy pattern matching is no different from regular pattern matching.
I think you're right, I was being stupid. Oh, well, it's late here

On Mon, Oct 6, 2008 at 9:48 PM, Andrew Coppin
Andrew Coppin wrote:
I have some longwinded code that works, but I'm still thinking about how to do this more elegantly. It looks like what I really need is something like
type M = StateT State (ResultSetT (ErrorT ErrorType Identity))
Is that the correct ordering?
If so, I guess that means I have to somehow construct ResultSetT. Is there an easy way to do that, given that I already have ResultSet? For example, if I put ResultSet into Traversable, would that let me do it?
...and again I'm talking to myself... :-/
So after much experimentation, I have managed to piece together the following facts:
- It appears that the outer-most monad transformer represents the inner-most monad. So "StateT Foo ListT" means a list of stateful computations, while "ListT (StateT Foo)" means a stateful list of computations.
Have you read "Monad Transformers Step by Step" [1] by Martin Grabmueller? It's a fantastic introduction to these beasties, leading the reader through a series of transformations from pure code to using about 4 different monads/transformers for all sorts of extra features. Seriously recommend it. []: http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.pdf Cheers, D

On Mon, Oct 6, 2008 at 4:48 PM, Andrew Coppin
Andrew Coppin wrote:
I have some longwinded code that works, but I'm still thinking about how to do this more elegantly. It looks like what I really need is something like
type M = StateT State (ResultSetT (ErrorT ErrorType Identity))
Is that the correct ordering?
Pretty much.
For reference, I humbly present ResultSet.hs:
There are actually several ways to make ResultSetT from ResultSet,
depending on how you want to handle the inner monad. There are two
popular ways to make a transformer variant of [], of which the easier
looks something like this:
newtype ListT m a = ListT { unListT :: m (Stream m a) }
data Stream m a = Nil | Cons a (m (Stream m a))
Using that and your code as a pattern, I've come up with the guts of a
similar transformer, included below. Like your code, it maintains a
list of answers at each depth. The effects of each depth are deferred
until some code (e.g., to_list) demands it, but the effects associated
with any answer at a given depth are linked. The resulting code, I
imagine, is not very efficient, but it shouldn't be too awful. I've
tried to keep things structurally similar to your code, to hopefully
make it clearer what is happening.
I also recommend trying alternatives like Oleg's FBackTrackT. In that
code, "mplus" corresponds to "union".
http://okmij.org/ftp/Haskell/FBackTrackT.hs
====
import Control.Monad
newtype ResultSetT m a = Pack { unpack :: m (Stream m a) }
data Stream m a = Nil | Cons [a] (m (Stream m a))
-- this is just the important parts, the rest should be fairly straightforward.
raw_lift :: (Monad m) => m a -> m (Stream m a)
raw_lift = liftM (\x -> Cons [x] (return Nil))
raw_union :: (Monad m) => Stream m a -> Stream m a -> Stream m a
raw_union Nil yss = yss
raw_union xss Nil = xss
raw_union (Cons xs xss) (Cons ys yss) = Cons (xs ++ ys) (liftM2
raw_union xss yss)
raw_bind :: (Monad m) => m (Stream m a) -> (a -> m (Stream m b)) -> m
(Stream m b)
raw_bind xss f = xss >>= work (return Nil)
where
work out Nil = out
work out (Cons xs xss) = do
yss <- foldr (liftM2 raw_union) out $ map f xs
return undefined
case yss of
Nil -> return $ Cons [] (xss >>= work (return Nil))
Cons ys yss -> return $ Cons ys (xss >>= work yss)
from_list :: (Monad m) => [[a]] -> ResultSetT m a
from_list = Pack . foldr (\xs xss -> return $ Cons xs xss) (return Nil)
to_list :: (Monad m) => ResultSetT m a -> m [[a]]
to_list (Pack m) = m >>= work
where
work Nil = return [[]]
work (Cons xs xss) = liftM (xs:) (xss >>= work)
limit :: (Monad m) => Int -> ResultSetT m a -> ResultSetT m a
limit n (Pack xss) = Pack (xss >>= work n)
where
work n (Cons xs xss) | n > 0 = return $ Cons xs (xss >>= work (n-1))
work _ _ = return Nil
--
Dave Menendez

Andrew Coppin wrote:
Consider the following beautiful code:
run :: State -> Foo -> ResultSet State
run_and :: State -> Foo -> Foo -> ResultSet State run_and s0 x y = do s1 <- run s0 x s2 <- run s1 y return s2
run_or :: State -> Foo -> Foo -> ResultSet State run_or s0 x y = merge (run s0 x) (run s0 y)
Right, well, it turns out that if I replace every ResultSet State with ErrorT ErrorType ResultSet State then the run_and function still typechecks! (I have no idea whether it still produces the correct result, but it typechecks.) The run_or function now becomes highly problematic. The function runErrorT essentially ends up being runErrorT :: ErrorT ErrorType ResultSet State -> Either ErrorType (ResultSet State) which looks promising. But that means I end up with runErrorT (run s0 x) :: ResultSet (Either ErrorType State) which isn't what I want at all. What *I* want is something more like Either ErrorType (ResultSet State). After much searching (Hoogle rather failed me here), I discover that if ResultSet happened to be in Traversable then I'd have a function called "sequence" which performs the exact type transformation I want. Then, utilising the fact that Either is itself a kind of error monad, I can do run_or s0 x y = let either_rset1 = sequence $ run s0 x either_rset2 = sequence $ run s0 y either_rset3 = do rset1 <- either_rset1; rset2 <- either_rset2; return (merge rset1 rset2) However, now I have a problem. I have either_rset3 :: Either ErrorType (ResultSet State), and I need to somehow get back to ErrorT ErrorType ResultSet State. Well, the first part is easy: case either_rset3 of Left e -> throwError e Right rset -> uh... Now I need some function from ResultSet State to ErrorT ErrorType ResultSet State. It looks like such a function ought to exist, but... uh... well I had to use Hoogle to find it. After some poking, it found a function called "lift" from a module I didn't even know about called Control.Monad.Trans. This has the exact signature I want, so we have run_or s0 x y = let either_rset1 = sequence $ run s0 x either_rset2 = sequence $ run s0 y either_rset3 = do rset1 <- either_rset1; rset2 <- either_rset2; return (merge rset1 rset2) in case either_rset3 of Left e -> throwError e Right rset -> lift rset Again, this now typechecks. I have *no clue* if it behaves correctly. (Most specifically, I've only tried using it with dummy types to see if the type checker will swallow it, so I haven't attempted writing an instance for Traversable yet. Maybe I'll go look at the list definition for this to see how it works...) So, assuming all this stuff does what I *think* it does, it looks like I've got this working. But _damn_, couldn't they have written down instructions somewhere? This has taken me all day...! o_O

Andrew Coppin wrote:
After much searching (Hoogle rather failed me here), I discover that...
I could probably elaborate on that point further. Try doing a Hoogle search for "c1 (c2 x) -> c2 (c1 x)". Hoogle correctly states that Data.Traversable.sequence will do it for you. Now try doing "c1 k (c2 x) -> c2 (c1 k x)". The 'sequence' function will also do this, but now Hoogle returns 0 results. This is puzzling, since AFAIK, the above two type signatures are "equvilent" in some sense. (Specifically, replace every type X with type Y and you get from one to the other.) To me, this looks like a Hoogle bug. (It goes without saying that Hoogle also failed to find anything for the more specific type signature I was searching for, despite the fact that 'sequence' unifies with it.) Is this a known issue?

Hi
Try doing a Hoogle search for "c1 (c2 x) -> c2 (c1 x)". Hoogle correctly states that Data.Traversable.sequence will do it for you.
Now try doing "c1 k (c2 x) -> c2 (c1 k x)". The 'sequence' function will also do this, but now Hoogle returns 0 results.
This is puzzling, since AFAIK, the above two type signatures are "equvilent" in some sense. (Specifically, replace every type X with type Y and you get from one to the other.) To me, this looks like a Hoogle bug. (It goes without saying that Hoogle also failed to find anything for the more specific type signature I was searching for, despite the fact that 'sequence' unifies with it.)
Hoogle is not a "unification engine" - since that is very rarely what people want out of a type search engine. What it is is an approximate matcher. Let's compare the two types: Your search :: c1 k (c2 x) -> c2 (c1 k x) sequence :: Monad m => [m a] -> m [a] Are you expecting c1 (:: * -> * -> *) to unify with [] (:: * -> *)? That seems kind incorrect at the very last. Additionally, those types don't look all that close. But, let's briefly consider unification (and why Hoogle doesn't used it). Consider the search: Eq a => [(a,b)] -> a -> b What the user wants is lookup, which sadly doesn't unify. However, undefined unifies perfectly. Thanks Neil ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

Mitchell, Neil wrote:
Hi
Try doing a Hoogle search for "c1 (c2 x) -> c2 (c1 x)". Hoogle correctly states that Data.Traversable.sequence will do it for you.
Now try doing "c1 k (c2 x) -> c2 (c1 k x)". The 'sequence' function will also do this, but now Hoogle returns 0 results.
This is puzzling, since AFAIK, the above two type signatures are "equvilent" in some sense. (Specifically, replace every type X with type Y and you get from one to the other.) To me, this looks like a Hoogle bug. (It goes without saying that Hoogle also failed to find anything for the more specific type signature I was searching for, despite the fact that 'sequence' unifies with it.)
Hoogle is not a "unification engine" - since that is very rarely what people want out of a type search engine. What it is is an approximate matcher. Let's compare the two types:
Your search :: c1 k (c2 x) -> c2 (c1 k x)
sequence :: Monad m => [m a] -> m [a]
Actually, I was thinking more along the lines of Data.Traversable.sequence, which has sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
Are you expecting c1 (:: * -> * -> *) to unify with [] (:: * -> *)? That seems kind incorrect at the very last. Additionally, those types don't look all that close.
Well, as I said, replacing one term with another transforms one signature into the other. I guess you can't curry type constructors as easily as functions - or at least, Hoogle currently doesn't like it.
But, let's briefly consider unification (and why Hoogle doesn't used it). Consider the search:
Eq a => [(a,b)] -> a -> b
What the user wants is lookup, which sadly doesn't unify. However, undefined unifies perfectly.
I see... I notice that x -> y doesn't unify with y -> x in any way, shape or form, but Hoogle has absolutely no problem with that. What *does* Hoogle actually use for matching? Just a set of huristics and a metric for how "similar" two signatures are so it can order by approximate similarity? Or is it something more scientific than that?

Actually, I was thinking more along the lines of Data.Traversable.sequence, which has
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
Are you expecting c1 (:: * -> * -> *) to unify with [] (:: * -> *)? That seems kind incorrect at the very last. Additionally, those types don't look all that close.
Well, as I said, replacing one term with another transforms one signature into the other. I guess you can't curry type constructors as easily as functions - or at least, Hoogle currently doesn't like it.
Yes, currying of type constructors is much less common, and entirely unsupported by Hoogle. Is there a general need for Hoogle to deal with curried type constructors? I'd not really considered it significantly.
But, let's briefly consider unification (and why Hoogle doesn't used it). Consider the search:
Eq a => [(a,b)] -> a -> b
What the user wants is lookup, which sadly doesn't unify. However, undefined unifies perfectly.
I see...
I notice that x -> y doesn't unify with y -> x in any way, shape or form, but Hoogle has absolutely no problem with that.
Hoogle has a problem with it, but not a severe problem. If you use the command line version you can type --verbose to get a list of the penalty points Hoogle has applied to a match.
What *does* Hoogle actually use for matching? Just a set of huristics and a metric for how "similar" two signatures are so it can order by approximate similarity? Or is it something more scientific than that?
It's more scientific than that, see http://www.wellquite.org/anglohaskell2008/ There will be a paper on Hoogle type matching at some point! Thanks Neil ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

Mitchell, Neil wrote:
Well, as I said, replacing one term with another transforms one signature into the other. I guess you can't curry type constructors as easily as functions - or at least, Hoogle currently doesn't like it.
Yes, currying of type constructors is much less common, and entirely unsupported by Hoogle. Is there a general need for Hoogle to deal with curried type constructors? I'd not really considered it significantly.
And I had just "assumed" this would work. If I ask for a function x -> y Hoogle manages to offer my functions like k -> x -> y which can be curried to give me the thing I want, I just assumed that an equivilent type wouldn't phase it. Ah well.
What *does* Hoogle actually use for matching? Just a set of huristics and a metric for how "similar" two signatures are so it can order by approximate similarity? Or is it something more scientific than that?
It's more scientific than that, see http://www.wellquite.org/anglohaskell2008/
I had a look at your slides. Looks like interesting stuff! Irritating as it is that Hoogle didn't help me find the function I wanted on this occasion, I still think it's really neat that a program like Hoogle can actually exist in the first place. And considering that with parametric polymorphism, the type signature "almost" tells you what the function does... very useful stuff. For my current troubles, it would be really useful if there were some program that you could feed some source code to, and it would tell you what the inferred types of each subexpression are. (Ideally it would be nice if you could use this on fragments that don't typecheck; being able to see what types are being inferred where could help explain why the type checker is unhappy, and ultimately where you went wrong. But I'm not sure how you could present the internal state in a digestible way.) I don't know if anybody has ever attempted such a tool...?

On Tue, Oct 7, 2008 at 7:09 PM, Andrew Coppin
For my current troubles, it would be really useful if there were some program that you could feed some source code to, and it would tell you what the inferred types of each subexpression are. (Ideally it would be nice if you could use this on fragments that don't typecheck; being able to see what types are being inferred where could help explain why the type checker is unhappy, and ultimately where you went wrong. But I'm not sure how you could present the internal state in a digestible way.) I don't know if anybody has ever attempted such a tool...?
There is such a tool, it's called ghci :) It just takes a bit of massaging to do what you want: ... some module code ... {- function_that_does_not_typecheck = some_expression -} function_that_does_not_typecheck = error "force typechecker to be happy" For now lets assume that you are curious about the type of the subexpression f some_func [a..b] where f, a, and b are locally bound. Then ghci> :set -fglasgow-exts ghci> :t (?f some_func [?a .. ?b]) Here's an example: Prelude> :t ?f map [?a .. ?b] ?f map [?a .. ?b] :: forall t a b t1. (Enum t1, ?b::t1, ?a::t1, ?f::((a -> b) -> [a] -> [b]) -> [t1] -> t) => t This tells you the types the variables have to have, and the type of the expression. Judicious use of (undefined :: type_signature) can also help. -- ryan

Ryan Ingram wrote:
There is such a tool, it's called ghci :) It just takes a bit of massaging to do what you want:
ghci> :set -fglasgow-exts ghci> :t (?f some_func [?a .. ?b])
Here's an example: Prelude> :t ?f map [?a .. ?b] ?f map [?a .. ?b] :: forall t a b t1. (Enum t1, ?b::t1, ?a::t1, ?f::((a -> b) -> [a] -> [b]) -> [t1] -> t) => t
This tells you the types the variables have to have, and the type of the expression.
Judicious use of (undefined :: type_signature) can also help.
Using undefined is already a standard technique for me. But what it doesn't let you do is foo (undefined :: Bar x) (undefined) :: Bar y -- What type is the second argument? I'm curios as to how the example you give actually works - I don't recognise that syntax at all...

The syntax is for the implicit parameter extension[1]. I think you would
write your example as
foo (undefined :: Bar x) ?z :: Bar y
Then querying the type of that whole expression with :t will list ?z's type
in the expression's constraints. (Of course, you should turn off the
monomorphism restriction so that ghc doesn't complain if constraints aren't
resolved).
[1]:
http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extension...
Reiner
On Thu, Oct 9, 2008 at 6:11 AM, Andrew Coppin
Ryan Ingram wrote:
There is such a tool, it's called ghci :) It just takes a bit of massaging to do what you want:
ghci> :set -fglasgow-exts ghci> :t (?f some_func [?a .. ?b])
Here's an example: Prelude> :t ?f map [?a .. ?b] ?f map [?a .. ?b] :: forall t a b t1. (Enum t1, ?b::t1, ?a::t1, ?f::((a -> b) -> [a] -> [b]) -> [t1] -> t) => t
This tells you the types the variables have to have, and the type of the expression.
Judicious use of (undefined :: type_signature) can also help.
Using undefined is already a standard technique for me. But what it doesn't let you do is
foo (undefined :: Bar x) (undefined) :: Bar y -- What type is the second argument?
I'm curios as to how the example you give actually works - I don't recognise that syntax at all...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2008/10/9 Reiner Pope
The syntax is for the implicit parameter extension[1]. I think you would write your example as
foo (undefined :: Bar x) ?z :: Bar y
Then querying the type of that whole expression with :t will list ?z's type in the expression's constraints. (Of course, you should turn off the monomorphism restriction so that ghc doesn't complain if constraints aren't resolved).
Oh yeah, I forgot about that. ghci> :set -fno-monomorphism-restriction Although I don't know if that affects the results of the :t command.
[1]: http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extension...
Reiner
There's also a haskell98 way to do the same thing, it's just a bit more wordy at the ghci prompt, and a bit more work to decode the result: ghci> :t \z -> (foo (undefined :: Bar x) z :: Bar y) Now, the type of this expression is clearly type of z -> Bar y So just read the value before the arrow to get your answer. -- ryan

Ryan Ingram wrote:
There's also a haskell98 way to do the same thing, it's just a bit more wordy at the ghci prompt, and a bit more work to decode the result:
ghci> :t \z -> (foo (undefined :: Bar x) z :: Bar y)
Now, the type of this expression is clearly
type of z -> Bar y
So just read the value before the arrow to get your answer.
Ah, ingenious! Why did I not think of that...?

Reiner Pope wrote:
The syntax is for the implicit parameter extension[1]. I think you would write your example as
foo (undefined :: Bar x) ?z :: Bar y
Then querying the type of that whole expression with :t will list ?z's type in the expression's constraints. (Of course, you should turn off the monomorphism restriction so that ghc doesn't complain if constraints aren't resolved).
[1]: http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extension...
Woah... that's some pretty crazy stuff, right there. Just wow. It would take me months to comprehend how that works. Heh. Oh well, it's useful for debugging the type system though. ;-)

Andrew Coppin wrote:
run_or s0 x y = let either_rset1 = sequence $ run s0 x either_rset2 = sequence $ run s0 y either_rset3 = do rset1 <- either_rset1; rset2 <- either_rset2; return (merge rset1 rset2) in case either_rset3 of Left e -> throwError e Right rset -> lift rset
Do you realise, this single snippet of code utilises the ErrorT monad [transformer], the ResultSet monad, *and* the Either monad, all in the space of a few lines?? That's three monads in one function! o_O I scare *myself*, I don't know about you guys...

Andrew Coppin wrote:
run_or s0 x y = let either_rset1 = sequence $ run s0 x either_rset2 = sequence $ run s0 y either_rset3 = do rset1 <- either_rset1; rset2 <- either_rset2; return (merge rset1 rset2) in case either_rset3 of Left e -> throwError e Right rset -> lift rset
Just to expand on that discussion of Control.Monad.ap aka. (Control.Applicative.<*>) in the other half of the thread. The expression do rset1 <- either_rset1 rset2 <- either_rset2 return (merge rset1 rset2) follows exactly the pattern Applicative is made for: We execute some actions, and combine their result using a pure function. Which action we execute is independent from the result of the previous actions. That means that we can write this expression as: return merge `ap` either_rset1 `ap` either_rset2 Note how we avoid to give names to intermediate results just to use them in the very next line. Since return f `ap` x == f `fmap` x, we can write shorter merge `fmap` either_rset1 `ap` either_rset2 Or in Applicative style: merge <$> either_rset1 <*> either_rset2 Now that the expression is somewhat shorter, we can inline the either_rset1, 2 and 3 as follows: case merge <$> sequence (run s0 x) <*> sequence (run s0 y) of Left e -> throwError e Right rset -> lift rset Note how the structure of the code reflects what happens. The structure is merge <$> ... <*> ..., and the meaning is: merge is called on two arguments, which are created by running some actions, and the result is again an action. While we are one it, we can get rid of the pattern matching by employing the either function as follows: either throwError lift (merge <$> sequence (run s0 x) <*> sequence (run s0 y))
Do you realise, this single snippet of code utilises the ErrorT monad [transformer], the ResultSet monad, *and* the Either monad, all in the space of a few lines?? That's three monads in one function! o_O
Now it fits on a single line! Tillmann

On Thu, 2 Oct 2008, Andrew Coppin wrote:
Consider the following beautiful code:
run :: State -> Foo -> ResultSet State
run_and :: State -> Foo -> Foo -> ResultSet State run_and s0 x y = do s1 <- run s0 x s2 <- run s1 y return s2
run_or :: State -> Foo -> Foo -> ResultSet State run_or s0 x y = merge (run s0 x) (run s0 y)
That works great. Unfortunately, I made some alterations to the functionallity the program has, and now it is actually possible for 'run' to fail. When this happens, a problem should be reported to the user. (By "user" I mean "the person running my compiled application".) After an insane amount of time making my head hurt, I disocvered that the type "Either ErrorType (ResultSet State)" is actually a monad. (Or rather, a monad within a monad.) Unfortunately, this causes some pretty serious problems:
run :: State -> Foo -> Either ErrorType (ResultSet State)
You may also like to use: http://hackage.haskell.org/packages/archive/explicit-exception/0.0.1/doc/htm...
participants (16)
-
Andrew Coppin
-
Anton van Straaten
-
Brandon S. Allbery KF8NH
-
Daniel Fischer
-
David Menendez
-
Dougal Stanton
-
Henning Thielemann
-
Jake McArthur
-
Jonathan Cast
-
Mitchell, Neil
-
Reid Barton
-
Reiner Pope
-
Robert Greayer
-
Ryan Ingram
-
Tillmann Rendel
-
wren ng thornton