>> 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]

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

Reply via email to