
I posted something similar about an hour ago but it seems to have gotten lost. Very strange. I've read that Monads can combine computations. Can a Maybe monad be combined with a List monad such that Nothing `mplus` [] ==> [] Just 1 `mplus` [] ==> [1] If not, can someone supply a simple example of combining computations? Michael

mplus requires both arguments to be in the same monad (the same type,
even). Fortunately, the empty list behaves like Nothing, and a singleton
list behaves like Just. So convert the Maybe before composing, using:
maybeToList Nothing = []
maybeToList (Just x) = [x]
(The maybeToList function can be found in Data.Maybe)
Keep in mind that this will give you:
Just 1 `mplus` [2,3,4] ==> [1,2,3,4]
Which may not be what you want...
Luke
On Sat, May 2, 2009 at 9:26 PM, michael rice
I posted something similar about an hour ago but it seems to have gotten lost. Very strange.
I've read that Monads can combine computations. Can a Maybe monad be combined with a List monad such that
Nothing `mplus` [] ==> [] Just 1 `mplus` [] ==> [1]
If not, can someone supply a simple example of combining computations?
Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, May 3, 2009 at 4:41 AM, Luke Palmer
mplus requires both arguments to be in the same monad (the same type, even). Fortunately, the empty list behaves like Nothing, and a singleton list behaves like Just. So convert the Maybe before composing, using:
maybeToList Nothing = [] maybeToList (Just x) = [x]
(The maybeToList function can be found in Data.Maybe)
Keep in mind that this will give you:
Just 1 `mplus` [2,3,4] ==> [1,2,3,4]
Silly me: maybeToList (Just 1) `mplus` [2,3,4] ==> [1,2,3,4]
Which may not be what you want...
Luke
On Sat, May 2, 2009 at 9:26 PM, michael rice
wrote: I posted something similar about an hour ago but it seems to have gotten lost. Very strange.
I've read that Monads can combine computations. Can a Maybe monad be combined with a List monad such that
Nothing `mplus` [] ==> [] Just 1 `mplus` [] ==> [1]
If not, can someone supply a simple example of combining computations?
Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I don't know if I understood your intentions, but let's go. The problem is that you're trying to combine different monads. We have mplus :: MonadPlus m => m a -> m a -> m a, so you never leave 'm', but you want mplus' :: ??? => n a -> m a -> m a where 'n' could be a different monad. In some specific cases where you know the internal structure of the monad, you can write 'mplus'', for example: mplus' :: MonadPlus m => Maybe a -> m a -> m a mplus' m l = maybeToMonad m `mplus` l maybeToMonad :: Monad m => Maybe a -> m a maybeToMonad = maybe (fail "Nothing") return In general, however, this operation can't be done. For example, how would you write: mplus' :: IO a -> [a] -> [a] ? HTH, -- Felipe.

mplus' :: MonadPlus m => Maybe a -> m a -> m a mplus' m l = maybeToMonad m `mplus` l
maybeToMonad :: Monad m => Maybe a -> m a maybeToMonad = maybe (fail "Nothing") return
In general, however, this operation can't be done. For example, how would you write:
mplus' :: IO a -> [a] -> [a]
Perhaps the question should be: is there an interesting structure that would allow us to capture when this kind of merging Monads is possible? We can convert every 'Maybe a' to a '[] a', but the other way round is partial or loses information, so lets focus on the first direction. Should there be a type family Up m1 m2 type instance Up Maybe [] = [] so that one could define mplusUp :: m1 a -> m2 a -> (m1 `Up` m2) a ? Well, we'd need the conversions, too, so perhaps {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies, TypeOperators #-} import Control.Monad class Up m1 m2 where type m1 :/\: m2 :: * -> * up :: m1 a -> m2 a -> ((m1 :/\: m2) a, (m1 :/\: m2) a) instance Up m m where type m :/\: m = m up ma1 ma2 = (ma1, ma2) instance Up Maybe [] where type Maybe :/\: [] = [] up m1a m2a = (maybe [] (:[]) m1a, m2a) instance Up [] Maybe where type [] :/\: Maybe = [] up m1a m2a = (m1a, maybe [] (:[]) m2a) mplusUp :: (m ~ (m1 :/\: m2), Up m1 m2, MonadPlus m) => m1 a -> m2 a -> m a m1a `mplusUp` m2a = mUp1a `mplus` mUp2a where (mUp1a,mUp2a) = up m1a m2a Whether or not that is interesting, or whether it needs to be defined differently to correspond to an interesting structure, I'll leave to the residential (co-)Categorians!-) Claus

On May 3, 2009, at 16:59 , Claus Reinke wrote:
Perhaps the question should be: is there an interesting structure that would allow us to capture when this kind of merging Monads is possible? We can convert every 'Maybe a' to a '[] a', but the other way round is partial or loses information, so lets focus on the first direction. Should there be a
It feels to me kinda like numeric upconversion. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Claus Reinke wrote:
mplus' :: MonadPlus m => Maybe a -> m a -> m a mplus' m l = maybeToMonad m `mplus` l
maybeToMonad :: Monad m => Maybe a -> m a maybeToMonad = maybe (fail "Nothing") return
In general, however, this operation can't be done. For example, how would you write:
mplus' :: IO a -> [a] -> [a]
Perhaps the question should be: is there an interesting structure that would allow us to capture when this kind of merging Monads is possible?
For me, it seems that Foldable is the other side of Alternative. A functor F supports Alternative if (F a) supports a monoidal structure for the construction of values, and it supports Foldable if (F a) supports a monoidal structure for the decomposition of values. That means that we can give a translation from every Foldable functor to every Alternative functor as follows: foldable2alternative = foldr (<|>) empty . fmap pure Tillmann

Am Sonntag 03 Mai 2009 05:26:22 schrieb michael rice:
I posted something similar about an hour ago but it seems to have gotten lost. Very strange.
I've read that Monads can combine computations. Can a Maybe monad be combined with a List monad such that
Nothing `mplus` [] ==> [] Just 1 `mplus` [] ==> [1]
Not directly, the type of mplus is mplus :: MonadPlus m => m a -> m a -> m a , so the monad has to be the same for both arguments. For [] and Maybe, you can use maybeToList and listToMaybe to convert one into the other: Prelude Data.Maybe Control.Monad> maybeToList Nothing [] Prelude Data.Maybe Control.Monad> maybeToList (Just 1) [1] Prelude Data.Maybe Control.Monad> maybeToList Nothing `mplus` [1] [1] Prelude Data.Maybe Control.Monad> maybeToList (Just 1) `mplus` [] [1] Prelude Data.Maybe Control.Monad> Nothing `mplus` listToMaybe [1] Just 1 Prelude Data.Maybe Control.Monad> Nothing `mplus` listToMaybe [1,2,3] Just 1 , for certain other combinations, you can also have a meaningful conversion from one monad to another (e.g. stateToStateT :: Monad m => State s a -> StateT s m a stateToStateT comp = StateT (return . runState comp) ) and employ the technique to combine them, but it's of limited use. A monad allows you to combine computations of 'similar' type (for some fuzzy meaning of similar), using (>>=), (>>) to combine them sequentially and perhaps mplus to combine them 'in parallel'.
If not, can someone supply a simple example of combining computations?
Michael
participants (7)
-
Brandon S. Allbery KF8NH
-
Claus Reinke
-
Daniel Fischer
-
Felipe Lessa
-
Luke Palmer
-
michael rice
-
Tillmann Rendel