[Haskell-cafe] Stacking monads

Andrew Coppin andrewcoppin at btinternet.com
Fri Oct 3 15:43:22 EDT 2008


David Menendez wrote:
> On Fri, Oct 3, 2008 at 1:39 PM, Andrew Coppin
> <andrewcoppin at btinternet.com> 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.



More information about the Haskell-Cafe mailing list