
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

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

On Nov 22, 2007 1:22 PM, 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
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

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 (>=>)(...):>
(>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (>=>) f g a = f a >>= g (...)
I always learn a lot in this list. Here is my >*> operator, that helps the code I was actually trying to write. Feel free to send it to obfuscated monad composition context. Thanks for the tips, Maurício ----------- module Main (Main.main) where import Control.Monad import System.IO (>*>) :: Monad m => m () -> (a -> m ()) -> (a -> m ()) (>*>) f f' = \a -> do{ f; f' a; } main :: IO () main = mapM_ ((putStrLn "") >*> putStrLn) $ map show [1,2,3]

module Main (Main.main) where import Control.Monad import System.IO
(>*>) :: Monad m => m () -> (a -> m ()) -> (a -> m ()) (>*>) f f' = \a -> do{ f; f' a; }
main :: IO () main = mapM_ ((putStrLn "") >*> putStrLn) $ map show [1,2,3]
There is nothing wrong with that, but I would normally write: mapM_ (\a -> putStrLn "" >> putStrLn a) $ map show [1,2,3] ...i.e. I wouldn't be afraid of a lambda in a case like that. IME it's moderately common to have to do: mapM_ (\a -> some stuff >> something_with a >> some stuff) ll Jules

On Nov 23, 2007 6:24 PM, Jules Bean
...i.e. I wouldn't be afraid of a lambda in a case like that. IME it's moderately common to have to do:
mapM_ (\a -> some stuff >> something_with a >> some stuff) ll
This has terrible endweight. In this imperativesque case, I'd write: forM_ li $ \a -> do some stuff something with a some stuff Where forM_ is from Data.Foldable (but is easily written as flip mapM_). Luke

main :: IO () main = mapM_ ((putStrLn "") >*> putStrLn) $ map show [1,2,3]
A couple other ways to do this code. Without monad combinators main = mapM_ putStrLn . ("":) . intersperse "" . map show $ [1..3] With your combinator, but collapsing it so we don't map over the collection twice. main = mapM_ ((putStrLn "") >*> print) $ [1..3] - Hitesh

On Fri, 2007-11-23 at 23:01 +0100, Roberto Zunino wrote:
Maurício wrote:
main = mapM_ ((putStrLn "") >*> putStrLn) $ map show [1,2,3]
Using only standard combinators:
main = mapM_ ((putStrLn "" >>) . putStrLn) $ map show [1,2,3]
== mapM_ ((putStrLn "" >>) . putStrLn . show) [1,2,3] == mapM_ ((putStrLn "" >>) . print) [1,2,3]

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

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
participants (9)
-
Brandon S. Allbery KF8NH
-
Brent Yorgey
-
Hitesh
-
Jonathan Cast
-
Jules Bean
-
Luke Palmer
-
Maurício
-
Roberto Zunino
-
Thomas Schilling