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' :: I
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 l
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]
P
Thanks for all the help, everyone.
I think this stuff is starting to come together.
Michael
--- On Sun, 5/3/09, Tillmann Rendel wrote:
From: Tillmann Rendel
Subject: Re: [Haskell-cafe] Combining computations
To: "michael rice"
Cc: haskell-cafe@haskell.org
Date: Sunday, May 3, 200
Hi,
normally, one uses monads to express and combine computations in the
same monad. However, you can convert between some monads, e.g. from
Maybe to List:
import Data.Maybe (maybeToList)
> let m1 = Nothing
> let m2 = [1]
> let m3 = maybeToList m1 `mplus` m2
> let m1 = Just 1
>
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
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 s
On Sun, May 3, 2009 at 4:41 AM, Luke Palmer wrote:
> 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
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
michael rice schrieb:
> let m1 = Just 1
> let m2 = []
> let m3 = m1 `mplus` m2 ==> [1] --if the Maybe is not Nothing, add it to the
> list
>
> Or am I misunderstanding combining computations?
You just got the type of mplus wrong:
mplus :: (MonadPlus m) => m a -> m a -> m a
Note that
michael rice wrote:
> If you look at this stuff long enough it almost begins to make sense.
> Maybe. ;-)
>
> I've been messing around with MonadPlus and I understand its usage
> with the Maybe and List monads. Since one use of Monads is combining
> computations, how can I combine a Maybe with a Lis
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 exampl
If you look at this stuff long enough it almost begins to make sense. Maybe. ;-)
I've been messing around with MonadPlus and I understand its usage with the
Maybe and List monads. Since one use of Monads is combining computations, how
can I combine a Maybe with a List?
let m1 = Nothing
let m2 =
13 matches
Mail list logo