[Haskell-beginners] How Best to Deal with Nested Monads?

Michael Craig mkscrg at gmail.com
Thu Sep 15 07:53:20 CEST 2011


Oops, typos:

main = lst >>= sequenceMTAll . map (getB' >=> getC')

(and forget about lst')

Mike S Craig
(908) 328 8030


On Thu, Sep 15, 2011 at 1:49 AM, Michael Craig <mkscrg at gmail.com> wrote:

> Alright, I return from the land of transformers with a solution:
>
>
> import Control.Monad.Trans.Class
> import Control.Monad.Trans.Maybe
>
> main = sequenceMTAll (lst' >>= map (getB' >=> getC'))
>
> lst' = lift lst :: MaybeT m [a]
> getB' = MaybeT . getMB
> getC' = lift . getC
>
> sequenceMTAll :: (Monad m) => [MaybeT m a] -> m [a]
> sequenceMTAll (x:xs) = do
>     y <- runMaybeT x
>     case y of
>       Nothing -> sequenceMTAll xs
>       Just z -> sequenceMTAll xs >>= return . (z:)
> sequenceMTAll [] = return []
>
>
> (Of course in real code I'd just modify lst, getMB, getC, etc. to fit the
> new types. The crux here is sequenceMTAll.)
>
> Am I abusing Maybe too much?
>
> Mike S Craig
> (908) 328 8030
>
>
> On Thu, Sep 15, 2011 at 1:15 AM, Brent Yorgey <byorgey at seas.upenn.edu>wrote:
>
>> On Wed, Sep 14, 2011 at 09:21:04PM -0400, Michael Craig wrote:
>> > Brent: Thanks for reminding me about (>=>). Far more readable! But
>> regarding
>> > the sequence thing: I can think of all sorts of reasons why we'd want to
>> do
>> > a single traversal. How about when lst is long or infinite? In general,
>> it's
>> > more useful to produce output incrementally than all at once at the
>> > end.
>>
>> Yes, producing output incrementally is great!  My point is that
>> usually laziness will take care of it for you, without having to
>> worry about it specifically.
>>
>> In this particular case, most monads will not actually allow
>> incremental processing anyway.  For example, suppose m = Maybe.  Then
>> when mapping getMB over lst, any particular element could cause the
>> whole computation to fail.  So we cannot output anything based on the
>> first elements in the list until we have processed the entire list,
>> because until we get to the very end of the list we do not know
>> whether to begin by outputting 'Just' or 'Nothing'.
>>
>> -Brent
>>
>> >
>> > Mike S Craig
>> > (908) 328 8030
>> >
>> >
>> > On Wed, Sep 14, 2011 at 8:18 PM, Brent Yorgey <byorgey at seas.upenn.edu
>> >wrote:
>> >
>> > > On Wed, Sep 14, 2011 at 06:48:29PM -0400, Michael Craig wrote:
>> > > > Say we've got these types
>> > > >
>> > > > lst :: m [a]
>> > > > getMB :: a -> m (Maybe b)
>> > > > getC :: b -> m c
>> > > >
>> > > > and we want to map getMB and getC over the elements of lst, all the
>> while
>> > > > discarding elements x where getMB x == Nothing.
>> > > >
>> > > > (This could be generalized more by replacing Maybe with some monad
>> m',
>> > > but
>> > > > let's run with Maybe because it's easy to talk about.)
>> > > >
>> > > > The best I've got (after some help on IRC) is this
>> not-so-easy-to-read
>> > > > oneliner:
>> > > >
>> > > > lst >>= (\x -> mapM (liftM (liftM getC) (getMB x)) >>= sequence
>> > > > . catMaybes
>> > >
>> > > How about this:
>> > >
>> > >  lst >>= (mapM getMB >=> (return . catMaybes) >=> mapM getC)
>> > >
>> > > Everyone always forgets about (>=>).
>> > >
>> > > > This is hard to read, but it's also bad because we run sequence
>> twice
>> > > (once
>> > > > inside of mapM). If we want to do multiple things to each element of
>> lst,
>> > > it
>> > > > would be nice to process each element completely before moving on to
>> the
>> > > > next.
>> > >
>> > > I wouldn't worry about running sequence twice.  Processing things by
>> > > chaining whole-structure transformations is the Haskell Way (tm).  All
>> > > that business about "doing only one traversal" is for people
>> > > programming in strict languages to worry about. The compiler can often
>> > > turn a chain of wholesale transformations into a single traversal
>> > > anyway.  In short, I see no particular reason why it is "nice" to
>> > > process each element completely before moving on.  Isn't it nicer to
>> > > be able to think in a more modular style?
>> > >
>> > > -Brent
>> > >
>> > > _______________________________________________
>> > > Beginners mailing list
>> > > Beginners at haskell.org
>> > > http://www.haskell.org/mailman/listinfo/beginners
>> > >
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110915/8ae372b7/attachment-0001.htm>


More information about the Beginners mailing list