Switching monadic encapsulations

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

On Mon, Jun 28, 2004 at 02:59:39PM +0100, Graham Klyne wrote:
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.
Such a function is called a distributive law of m1 over m2 if it satisfies the following equations (subscripts added for readability): f . return_1 = liftM_2 return_1 f . liftM_1 return_2 = return_2 f . join_1 = liftM_2 join_1 . f . liftM_1 f f . liftM_1 join_2 = join_2 . liftM_2 f . f The composition m2.m1 can be made a monad in a standard way: return = return_2 . return_1 join = liftM_2 join_1 . join_2 . liftM_2 f if and only if such a distributive law exists. See section 9.2 of "Toposes, Triples and Theories", by Michael Barr and Charles Wells, online at http://www.cwru.edu/artsci/math/wells/pub/ttt.html ("triple" is another name for a monad)
[...], and sequence does for the List monad what I am seeking to generalize:
sequence :: [m a] -> m [a]
Yes, it's a distributive law of [] over m, but only if m is a commutative monad (lists are so sequential). Some more distributive laws: * the exception monad distributes over any other monad: either (return . Left) (liftM Right) :: Monad m => Either x (m a) -> m (Either x a) * so does the writer monad: uncurry (liftM . (,)) :: (Monoid w, Monad m) => (w, m a) -> m (w,a) * any monad distributes over the reader monad: flip (liftM . flip ($)) :: Monad m => m (r -> a) -> r -> m a

Graham Klyne writes:
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.
In order to do that, the two monads have to be composable. Mark Jones's paper "Functional Programming with Overloading and Higher-Order Polymorphism"[1] brings up a similar function while discussing monad composition and transformers: swap :: m (n a) -> n (m a) He ends up defining two classes of monads with appropriate swap functions: class Monad m => Into m where into :: Monad n => m (n a) -> n (m a) class Monad m => OutOf m where outof :: Monad n => n (m a) -> m (n a) List, Maybe, Error, and Writer are instances of Into, and Reader is an instance of OutOf. For Either String, the instance would be something like this: instance Into (Either String) where into (Left e) = return (Left e) into (Right m) = fmap Right m The only wrinkle is that Jones declares Monad as a subclass of Functor, but the Prelude doesn't for some reason. In that case, you could still use: into (Right m) = m >>= return . Right [1] http://www.cse.ogi.edu/~mpj/pubs/springschool.html
... map looks like a version of liftM specialized to lists: ... Similarly, concat appears to be a monadic join on lists.
They are. It's easier to see with a slightly different definition of
Monad:
class Functor f where
fmap :: (a -> b) -> f a -> f b
-- when f is a Monad and (>>=) is defined, fmap may be defined as
-- fmap f m = m >>= return . f
class Functor m => Monad m where
return :: a -> m a
join :: m (m a) -> m a
(>>=) :: m a -> (a -> m b) -> m b
(>>) :: m a -> m b -> m b
fail :: String -> m a
-- minimal definition: return and (>>=) or return, join, and fmap
join m = m >>= id
m >>= k = join (fmap k m)
m >> n = m >>= (\_ -> n)
fail s = error s
Then you can define the list monad like so:
instance Functor [] where
fmap = map
instance Monad [] where
return x = [x]
join = concat
fail _ = []
liftM plays the same role as fmap.
--
David Menendez
participants (3)
-
David Menendez
-
Graham Klyne
-
Ross Paterson