[Haskell-cafe] Stacking monads

David Menendez dave at zednenem.com
Thu Oct 2 18:01:24 EDT 2008


On Thu, Oct 2, 2008 at 3:40 PM, Andrew Coppin
<andrewcoppin at btinternet.com> 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.

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 <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list