[Haskell-cafe] Composing monads (sort of)

Nicolas Frisby nicolas.frisby at gmail.com
Sat Dec 16 16:29:47 EST 2006


Once I start needing to combine Maybe with other monads, I usually
take a moment to generalize the appropriate Maybe parts to MonadError
e m => m. Then we can just use the (ErrorT e IO) monad.

Nick

On 12/16/06, Pepe Iborra <mnislaih at gmail.com> wrote:
> Wait, there are two monads in scene here, IO and Maybe.
> The right solution is to compose them indeed. One could use the
> MaybeT monad transformer defined in the 'All about monads' tutorial
> [1], or we could just define the IOmaybe monad:
>
>  > import Data.Traversable (mapM)
>  >
>  > newtype IOMaybe a = IOM { iom :: IO (Maybe a) }
>  >
>  > instance Monad IOMaybe where
>  >     return = IOM . return . Just
>  >     c >>= f = IOM$ do
>  >        mb_v <- iom c
>  >        mapM (iom.f) mb_v >>= return . join
>
> Now we can define:
>
>  > t1 = IOM . return . f1
>  > t2 = IOM . f2
>  > t3 = IOM . return . f3
>  > traverse rec1 = t1 rec1 >>= t2 >>= t3
>
> And this scheme lends itself very well to define any kind of traversal.
> Note that I used the more general version of mapM defined in
> Data.Traversable in the definition of the (>>=) combinator. A more
> conventional definition is given the 'All about monads' tutorial.
>
> Cheers
> pepe
>
> 1- http://www.nomaware.com/monads/html/index.html
>
> On 16/12/2006, at 15:35, Chris Eidhof wrote:
>
> > Hey Mark,
> >
> >> How can I concisely compose these functions without having to
> >> write a cascade of case statements such as:
> >>
> >> case f1 rec1 of
> >>     Nothing -> return Nothing
> >>     Just id1 -> do
> >>                     rec2 <- f2 id2
> >>                     return $ case rec2 of
> >>                                 Nothing -> return Nothing
> >>                                 Just rec2' -> case f3 rec2' of
> >>                                                 ....
> >> I understand that if I was just dealing with Maybe I could use the
> >> fact that Maybe is a monad.
> > Yes, you can write like this:
> >
> >> id2 <- f1 rec1
> >> rec2 <- f2 id2
> >> rec3 <- f3 rec2
> >> return rec3
> > or, even shorter:
> >> id2 <- f1 rec1
> >> rec2 <- f2 id2
> >> f3 rec2
> >
> > The cool thing of the Maybe monad is that it combines a result in
> > such a way that it removes the plumbing of constantly checking for
> > Nothing. I can definitely recommand you the following tutorials:
> >
> > http://www.nomaware.com/monads/html/index.html
> > http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.en.html
> >
> > Those two tutorials really helped me.
> >
> > Good luck,
> > Chris
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list