[Haskell-cafe] Switching monadic encapsulations

Graham Klyne gk at ninebynine.org
Mon Jun 28 09:59:39 EDT 2004


Is there a function that switches monadic layering?

     f :: (Monad m1,Monad m2) => m1 (m2 a) -> m2 (m1 a)

Does this even make sense in the general case?  I'm thinking along the 
lines of a generalization of sequence to non-list monads.

This question arises from a desire to generalize some error handling code, 
starting with:

    liftES :: (a->Either String [a]) -> Either String [a] -> Either String [a]

where (Either String) as used as an error monad.  A simple implementation 
of this might be:

    liftES _ (Left  er) = Left er
    liftES f (Right as) = sequence $ map f as

but I notice that liftES looks a little bit like liftM, and sequence does 
for the List monad what I am seeking to generalize:

    sequence :: [m a] -> m [a]

and map looks like a version of liftM specialized to lists:

    liftM f = \a -> do { a1 <- a ; return (f a1) }
            = \a -> ( a >>= \a1 -> return (f a1) )

when m is a list monad:

            = \a -> concat (map (\a1 -> [f a1]) a)

Similarly, concat appears to be a monadic join on lists.

My listES might be partially generalized to something like:

     liftX :: (r -> m [r]) -> m [r] -> m [r]
     liftX mf = \mb -> do { b1 <- mb ; liftM concat $ sequence $ map mf b }

the liftM here being used to apply 'concat' to achieve m [[r]] -> m [r].  I 
can see a possible replacement of concat with join and map with liftM, but 
I don't see any purely monadic equivalent for 'sequence'.  Hence the 
original question.

#g


------------
Graham Klyne
For email:
http://www.ninebynine.org/#Contact



More information about the Haskell-Cafe mailing list