[Haskell-cafe] Combining computations

2009-05-03 Thread michael rice
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 = [1]
let m3 = m1 `mplus` m2  == [1]    --if the Maybe is Nothing, do nothing  

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?

Michael




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Combining computations

2009-05-03 Thread 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


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tony Morris
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 List?

 let m1 = Nothing
 let m2 = [1]
 let m3 = m1 `mplus` m2  == [1]--if the Maybe is Nothing, do nothing 

 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?

 Michael


 

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
   

Hi Michael,
You'll want the Data.Maybe.listToMaybe and Data.Maybe.maybeToList functions.

-- 
Tony Morris
http://tmorris.net/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Kalman Noel
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 it takes two values of the same type (m a), but you're giving
it values of different types.  That is, combining computations of
different types is not within the scope of MonadPlus.  In this case, it
makes sense to convert (Just 1) to [1] via Data.Maybe.maybeToList, thus:

m1 = Just 1
m2 = [2,3]
m3 = maybeToList m1 `mplus` m2   -- [1,2,3]

Note also that, in this example, Monoid (mappend) instead of MonadPlus
(mplus) would be sufficient.  Actually MonadPlus becomes useful only
when you are concerned about the extra properties that its instances are
expected to satisfy.

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread 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]

Which may not be what you want...

Luke

On Sat, May 2, 2009 at 9:26 PM, michael rice nowg...@yahoo.com 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Luke Palmer
On Sun, May 3, 2009 at 4:41 AM, Luke Palmer lrpal...@gmail.com 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 = []
 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 nowg...@yahoo.com 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



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Felipe Lessa
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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Daniel Fischer
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tillmann Rendel

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
   let m2 = []
   let m3 = maybeToList m1 `mplus` m2


In fact, you can convert from Maybe to any MonadPlus.

  maybeToMonadPlus Nothing = mzero
  maybeToMonadPlus (Just x) = return x

And you can convert from List to any MonadPlus:

  listToMonadPlus Nothing  = []
  listToMonadPlus (x : xs) = return x `mplus` listToMonadPlus xs

Now you should be able to do:

  m1 = maybeToMonadPlus (Just 1)
  m2 = listtoMonadPlus [2, 3]
  m3 = m1 `mplus` m2 :: Just Int -- Just 1
  m4 = m1 `mplus` m2 :: [Int]-- [1, 2, 3]

The reason this is possible is that Maybe and List do not support 
additional effects beyond what is common to all MonadPlus instances.



Another option is to never specify which monad your computations are in 
in the first place. Instead, only specify which computational effects 
the monad should support.


  m1 = mzero:: MonadPlus m = m a
  m2 = return 1 :: (Monad m, Num a) = m a
  m3 = m1 `mplus` m2 `mplus` Just 2 -- Just 1
  m4 = m1 `mplus` m2 `mplus` [2, 3] -- [1, 2, 3]

In this version, m1 and m2 are polymorphic computations, which can be 
used together with List computations, Maybe computations, or any other 
MonadPlus instances. m1 needs MonadPlus, while m2 is happy with any 
Monad instance. This fact is encoded in their type.


  Tillmann
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread michael rice
Thanks for all the help, everyone.

I think this stuff is starting to come together.

Michael

--- On Sun, 5/3/09, Tillmann Rendel ren...@cs.au.dk wrote:

From: Tillmann Rendel ren...@cs.au.dk
Subject: Re: [Haskell-cafe] Combining computations
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Sunday, May 3, 2009, 7:33 AM

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
   let m2 = []
   let m3 = maybeToList m1 `mplus` m2


In fact, you can convert from Maybe to any MonadPlus.

  maybeToMonadPlus Nothing = mzero
  maybeToMonadPlus (Just x) = return x

And you can convert from List to any MonadPlus:

  listToMonadPlus Nothing  = []
  listToMonadPlus (x : xs) = return x `mplus` listToMonadPlus xs

Now you should be able to do:

  m1 = maybeToMonadPlus (Just 1)
  m2 = listtoMonadPlus [2, 3]
  m3 = m1 `mplus` m2 :: Just Int -- Just 1
  m4 = m1 `mplus` m2 :: [Int]    -- [1, 2, 3]

The reason this is possible is that Maybe and List do not support additional 
effects beyond what is common to all MonadPlus instances.


Another option is to never specify which monad your computations are in in the 
first place. Instead, only specify which computational effects the monad should 
support.

  m1 = mzero    :: MonadPlus m = m a
  m2 = return 1 :: (Monad m, Num a) = m a
  m3 = m1 `mplus` m2 `mplus` Just 2 -- Just 1
  m4 = m1 `mplus` m2 `mplus` [2, 3] -- [1, 2, 3]

In this version, m1 and m2 are polymorphic computations, which can be used 
together with List computations, Maybe computations, or any other MonadPlus 
instances. m1 needs MonadPlus, while m2 is happy with any Monad instance. This 
fact is encoded in their type.

  Tillmann



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Claus Reinke

 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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Brandon S. Allbery KF8NH

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] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tillmann Rendel

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe