[Haskell-cafe] Stacking monads

David Menendez dave at zednenem.com
Fri Oct 3 15:17:27 EDT 2008


On Fri, Oct 3, 2008 at 1:39 PM, Andrew Coppin
<andrewcoppin at btinternet.com> wrote:
> 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 <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list