Re: [Haskell-cafe] Composing monads

2007-11-23 Thread Jules Bean

Maurí­cio wrote:

Hi,

If I have two computations a-IO b
and b-IO c, can I join them to
get an a-IO c computation? I imagine
something like a liftM dot operator.


You've already been shown the = operator and how to define it from = 
by other answers.


Just for variety, here is how you would define it using do notation:

compose :: Monad m = (a - m b) - (b - m c) - a - m c
compose act act' a = do
  b - act a
  act' b

Jules


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


[Haskell-cafe] Composing monads

2007-11-22 Thread Maurí­cio

Hi,

If I have two computations a-IO b
and b-IO c, can I join them to
get an a-IO c computation? I imagine
something like a liftM dot operator.

Thanks,
Maurício

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


Re: [Haskell-cafe] Composing monads

2007-11-22 Thread Jonathan Cast

On 22 Nov 2007, at 10:17 AM, Maurí cio wrote:


Hi,

If I have two computations a-IO b
and b-IO c, can I join them to
get an a-IO c computation? I imagine
something like a liftM dot operator.


This is called Kleisli composition, by the way; it's defined as (=)  
in Control.Monad.


jcc

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


Re: [Haskell-cafe] Composing monads

2007-11-22 Thread Brandon S. Allbery KF8NH


On Nov 22, 2007, at 13:17 , Maurí cio wrote:


If I have two computations a-IO b
and b-IO c, can I join them to
get an a-IO c computation? I imagine
something like a liftM dot operator.


If you have GHC 6.8.1, this is the Kleisli composition operator (=)  
in Control.Monad.  (There is also (=) which corresponds to (=).)


Prelude Control.Monad :i (=)
(=) :: (Monad m) = (a - m b) - (b - m c) - a - m c
-- Defined in Control.Monad
infixr 1 =
Prelude Control.Monad :i (=)
(=) :: (Monad m) = (b - m c) - (a - m b) - a - m c
-- Defined in Control.Monad
infixr 1 =

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Composing monads

2007-11-22 Thread Brent Yorgey
On Nov 22, 2007 1:22 PM, Jonathan Cast [EMAIL PROTECTED] wrote:

 On 22 Nov 2007, at 10:17 AM, Maurí cio wrote:

  Hi,
 
  If I have two computations a-IO b
  and b-IO c, can I join them to
  get an a-IO c computation? I imagine
  something like a liftM dot operator.

 This is called Kleisli composition, by the way; it's defined as (=)
 in Control.Monad.

 jcc


Even if you didn't know about (=)  (I didn't, actually!), it's not too
hard to write yourself:

(=) :: (Monad m) = (a - m b) - (b - m c) - (a - m c)
(=) f g a = f a = g

There's no magic, just follow the types. =)

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


[Haskell-cafe] Composing monads (sort of)

2006-12-16 Thread Mark Wassell

Hi,

I have a set of functions:

f1 :: DBRecord - Maybe Int
f2 :: Int - IO Maybe DBRecord
f3 :: DBRecord - Maybe Int

The odd numbered functions are field accessors, accessing a field that 
might hold an identifier for another record. The even numbered functions 
are record fetch functions that get records from the database. I want to 
compose these so that I can navigate structures of joined records in the 
database.


How can I concisely compose these functions without having to write a 
cascade of case statements such as:


case f1 rec1 of
Nothing - return Nothing
Just id1 - do
rec2 - f2 id2
return $ case rec2 of
Nothing - return Nothing
Just rec2' - case f3 rec2' of

I understand that if I was just dealing with Maybe I could use the fact 
that Maybe is a monad. I am also not sure if composing the IO and the 
Maybe will get me what I want (some of the functions only return Maybe Int).


Cheers

Mark

PS Heard this on the 'West Wing' and thought it was appropriate in a way:

A coach goes up to a player and asks Are you ignorant or apathetic?. 
The player replies I don't know and I don't care.

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


Re: [Haskell-cafe] Composing monads (sort of)

2006-12-16 Thread Chris Eidhof

Hey Mark,

How can I concisely compose these functions without having to write  
a cascade of case statements such as:


case f1 rec1 of
Nothing - return Nothing
Just id1 - do
rec2 - f2 id2
return $ case rec2 of
Nothing - return Nothing
Just rec2' - case f3 rec2' of

I understand that if I was just dealing with Maybe I could use the  
fact that Maybe is a monad.

Yes, you can write like this:


id2 - f1 rec1
rec2 - f2 id2
rec3 - f3 rec2
return rec3

or, even shorter:

id2 - f1 rec1
rec2 - f2 id2
f3 rec2


The cool thing of the Maybe monad is that it combines a result in  
such a way that it removes the plumbing of constantly checking for  
Nothing. I can definitely recommand you the following tutorials:


http://www.nomaware.com/monads/html/index.html
http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.en.html

Those two tutorials really helped me.

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


Re: [Haskell-cafe] Composing monads (sort of)

2006-12-16 Thread Pepe Iborra

Wait, there are two monads in scene here, IO and Maybe.
The right solution is to compose them indeed. One could use the  
MaybeT monad transformer defined in the 'All about monads' tutorial 
[1], or we could just define the IOmaybe monad:


 import Data.Traversable (mapM)

 newtype IOMaybe a = IOM { iom :: IO (Maybe a) }

 instance Monad IOMaybe where
 return = IOM . return . Just
 c = f = IOM$ do
mb_v - iom c
mapM (iom.f) mb_v = return . join

Now we can define:

 t1 = IOM . return . f1
 t2 = IOM . f2
 t3 = IOM . return . f3
 traverse rec1 = t1 rec1 = t2 = t3

And this scheme lends itself very well to define any kind of traversal.
Note that I used the more general version of mapM defined in  
Data.Traversable in the definition of the (=) combinator. A more  
conventional definition is given the 'All about monads' tutorial.


Cheers
pepe

1- http://www.nomaware.com/monads/html/index.html

On 16/12/2006, at 15:35, Chris Eidhof wrote:


Hey Mark,

How can I concisely compose these functions without having to  
write a cascade of case statements such as:


case f1 rec1 of
Nothing - return Nothing
Just id1 - do
rec2 - f2 id2
return $ case rec2 of
Nothing - return Nothing
Just rec2' - case f3 rec2' of

I understand that if I was just dealing with Maybe I could use the  
fact that Maybe is a monad.

Yes, you can write like this:


id2 - f1 rec1
rec2 - f2 id2
rec3 - f3 rec2
return rec3

or, even shorter:

id2 - f1 rec1
rec2 - f2 id2
f3 rec2


The cool thing of the Maybe monad is that it combines a result in  
such a way that it removes the plumbing of constantly checking for  
Nothing. I can definitely recommand you the following tutorials:


http://www.nomaware.com/monads/html/index.html
http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.en.html

Those two tutorials really helped me.

Good luck,
Chris
___
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: Re: [Haskell-cafe] Composing monads (sort of)

2006-12-16 Thread Nicolas Frisby

Once I start needing to combine Maybe with other monads, I usually
take a moment to generalize the appropriate Maybe parts to MonadError
e m = m. Then we can just use the (ErrorT e IO) monad.

Nick

On 12/16/06, Pepe Iborra [EMAIL PROTECTED] wrote:

Wait, there are two monads in scene here, IO and Maybe.
The right solution is to compose them indeed. One could use the
MaybeT monad transformer defined in the 'All about monads' tutorial
[1], or we could just define the IOmaybe monad:

  import Data.Traversable (mapM)
 
  newtype IOMaybe a = IOM { iom :: IO (Maybe a) }
 
  instance Monad IOMaybe where
  return = IOM . return . Just
  c = f = IOM$ do
 mb_v - iom c
 mapM (iom.f) mb_v = return . join

Now we can define:

  t1 = IOM . return . f1
  t2 = IOM . f2
  t3 = IOM . return . f3
  traverse rec1 = t1 rec1 = t2 = t3

And this scheme lends itself very well to define any kind of traversal.
Note that I used the more general version of mapM defined in
Data.Traversable in the definition of the (=) combinator. A more
conventional definition is given the 'All about monads' tutorial.

Cheers
pepe

1- http://www.nomaware.com/monads/html/index.html

On 16/12/2006, at 15:35, Chris Eidhof wrote:

 Hey Mark,

 How can I concisely compose these functions without having to
 write a cascade of case statements such as:

 case f1 rec1 of
 Nothing - return Nothing
 Just id1 - do
 rec2 - f2 id2
 return $ case rec2 of
 Nothing - return Nothing
 Just rec2' - case f3 rec2' of
 
 I understand that if I was just dealing with Maybe I could use the
 fact that Maybe is a monad.
 Yes, you can write like this:

 id2 - f1 rec1
 rec2 - f2 id2
 rec3 - f3 rec2
 return rec3
 or, even shorter:
 id2 - f1 rec1
 rec2 - f2 id2
 f3 rec2

 The cool thing of the Maybe monad is that it combines a result in
 such a way that it removes the plumbing of constantly checking for
 Nothing. I can definitely recommand you the following tutorials:

 http://www.nomaware.com/monads/html/index.html
 http://uebb.cs.tu-berlin.de/~magr/pub/Transformers.en.html

 Those two tutorials really helped me.

 Good luck,
 Chris
 ___
 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


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