Proposal: Adding Kleisli composition to Control.Monad

http://hackage.haskell.org/trac/ghc/ticket/997 Add Kleisli composition to Control.Monad. Kleisli composition of monads is a foundational feature missing from the current Control.Monad library. A recent discussion revealed solid support for its inclusion. This patch adds: (>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c) Along with the useful control combinator: forever :: (Monad m) => m a -> m () Traditionally, >=> has been written as @@, however to support the flipped version, new notation seems to be required. It should be notated that there is overlap with the Kleisli class in Control.Arrow (specifically >>>), however, short of a convenient unifying form for Arrow and Monad, a monad-specific >>> seems reasonable. To mirror >>> and =<<, infixr 1 was chosen. Proposal period: 2 weeks. Deadline: 27th November. -- Don ------------------------------------------------------------------------ hunk ./Control/Monad.hs 40 + , (>=>) -- :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) + , (<=<) -- :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c) + , forever -- :: (Monad m) => m a -> m () hunk ./Control/Monad.hs 179 +infixr 1 <=<, >=> + +-- | Left-to-right Kleisli composition of monads. +(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) +f >=> g = \x -> f x >>= g + +-- | Right-to-left Kleisli composition of monads. '(>=>)', with the arguments flipped +(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) +(<=<) = flip (>=>) + +-- | @'forever' act@ repeats the action infinitely. +forever :: (Monad m) => m a -> m () +forever a = a >> forever a ------------------------------------------------------------------------

On Mon, 2006-11-13 at 13:15 +1100, Donald Bruce Stewart wrote:
[snip]
Along with the useful control combinator:
forever :: (Monad m) => m a -> m ()
[snip]
+-- | @'forever' act@ repeats the action infinitely. +forever :: (Monad m) => m a -> m () +forever a = a >> forever a
I would personally rather see repeatM and repeatM_ like the replicateM/replicateM_ pair already in Control.Monad. I implement them like this: repeatM = sequence . repeat repeatM_ = sequence_ . repeat Google CodeSearch tells me it's the way replicateM was implemented too: http://www.google.com/codesearch?hl=en&lr=&q=replicateM+file%3A%5C.hs% 24&btnG=Search Btw, i hope it is ok to give my opinion on this. Im asking since im not a library developer or anything just a normal programmer.

moonlite:
On Mon, 2006-11-13 at 13:15 +1100, Donald Bruce Stewart wrote:
[snip]
Along with the useful control combinator:
forever :: (Monad m) => m a -> m ()
[snip]
+-- | @'forever' act@ repeats the action infinitely. +forever :: (Monad m) => m a -> m () +forever a = a >> forever a
I would personally rather see repeatM and repeatM_ like the replicateM/replicateM_ pair already in Control.Monad.
I implement them like this: repeatM = sequence . repeat repeatM_ = sequence_ . repeat
Google CodeSearch tells me it's the way replicateM was implemented too: http://www.google.com/codesearch?hl=en&lr=&q=replicateM+file%3A%5C.hs% 24&btnG=Search
Btw, i hope it is ok to give my opinion on this. Im asking since im not a library developer or anything just a normal programmer.
On this topic, we can go back to: http://www.mail-archive.com/cvs-all@haskell.org/msg26511.html However, it was pointed out that repeatM is next to useless, and it is traditional to use 'forever' for repeatM_ (see for example "Tackling the Awkward Squad", and http://haskell.org/haskellwiki/Roll_your_own_IRC_bot That being said, repeatM_ isn't too bad, should people prefer it. -- Don

Hi
However, it was pointed out that repeatM is next to useless, and it is traditional to use 'forever' for repeatM_ (see for example "Tackling the Awkward Squad", and http://haskell.org/haskellwiki/Roll_your_own_IRC_bot
That being said, repeatM_ isn't too bad, should people prefer it.
If I had to guess what the monadic version of repeat was, I'd guess repeatM_ before forever. Forever is a very overloaded word, repeat in Haskell has exactly one concrete meaning agreed by everyone (since its in the Prelude). Thanks Neil

ndmitchell:
Hi
However, it was pointed out that repeatM is next to useless, and it is traditional to use 'forever' for repeatM_ (see for example "Tackling the Awkward Squad", and http://haskell.org/haskellwiki/Roll_your_own_IRC_bot
That being said, repeatM_ isn't too bad, should people prefer it.
If I had to guess what the monadic version of repeat was, I'd guess repeatM_ before forever. Forever is a very overloaded word, repeat in Haskell has exactly one concrete meaning agreed by everyone (since its in the Prelude).
Agreed. But 'forever' is a pretty special control structures, worthy of a special name. Consider the cuteness of: listen = forever $ do h <- get s <- io (hGetLine h) io (putStrLn s) if ping s then pong s else eval (clean s) versus: listen = repeatM_ $ do h <- get s <- io (hGetLine h) io (putStrLn s) if ping s then pong s else eval (clean s) Or, to quote the awkward squad, s2.4 "Control structures":
We can easily express an infinite loop as a combinator:
forever :: IO () -> IO () forever a = a >> forever a
I'm we're going to use this forever more, then a name more meaningful than repeatM_ might be appropriate (personally, I have to check every time whether it is replicate or repeat that is :: Int -> a -> [a]). -- Don

On Mon, Nov 13, 2006 at 02:27:12PM +1100, Donald Bruce Stewart wrote:
I'm we're going to use this forever more, then a name more meaningful than repeatM_ might be appropriate (personally, I have to check every time whether it is replicate or repeat that is :: Int -> a -> [a]).
now it will be three times easier to remember, as you only need to remember what one of repeat, repeatM, and repeatM_ do to easily determine what the other two do. standard naming conventions are very nice when they fit so well, as they do in this case. John -- John Meacham - ⑆repetae.net⑆john⑈

john:
On Mon, Nov 13, 2006 at 02:27:12PM +1100, Donald Bruce Stewart wrote:
I'm we're going to use this forever more, then a name more meaningful than repeatM_ might be appropriate (personally, I have to check every time whether it is replicate or repeat that is :: Int -> a -> [a]).
now it will be three times easier to remember, as you only need to remember what one of repeat, repeatM, and repeatM_ do to easily determine what the other two do. standard naming conventions are very nice when they fit so well, as they do in this case.
Ok :) I'll resubmit 'repeatM_' as a separate patch. -- Don

Hello Donald, Monday, November 13, 2006, 1:25:19 PM, you wrote:
I'm we're going to use this forever more, then a name more meaningful
i prefer 'forever' name -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Donald, Monday, November 13, 2006, 1:25:19 PM, you wrote:
I'm we're going to use this forever more, then a name more meaningful than repeatM_ might be appropriate (personally, I have to check every time whether it is replicate or repeat that is :: Int -> a -> [a]).
I'll resubmit 'repeatM_' as a separate patch.
i have one idea: this dispute between folks that prefer repeatM_ name and whose preferring forever form may just reflect differences between FP-oriented and imperative programming style. may be the best solution will be to create new Control.Imperative module and put all this imperative-alike stuff here. so, John Meacham can just ignore existence of such module while we can continue to decorate our imperative programs with such beautiful shortcuts: foreach = flip mapM for = flip mapM_ on = flip when forever = sequence_ . repeat new = newIORef (=:) = writeIORef ...... i'm pretty sure that for novices learning Haskell studying these names will be much simpler than studying Monad concepts and so on -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2006-11-17, Bulat Ziganshin
foreach = flip mapM for = flip mapM_ on = flip when forever = sequence_ . repeat new = newIORef (=:) = writeIORef ......
i'm pretty sure that for novices learning Haskell studying these names will be much simpler than studying Monad concepts and so on
Which will eventually handicap them. -- Aaron Denney -><-

Hello Aaron, Friday, November 17, 2006, 9:03:30 PM, you wrote:
i'm pretty sure that for novices learning Haskell studying these names will be much simpler than studying Monad concepts and so on
Which will eventually handicap them.
the key word here is "eventually" ;) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 11/17/06, Aaron Denney
On 2006-11-17, Bulat Ziganshin
wrote: foreach = flip mapM for = flip mapM_ on = flip when forever = sequence_ . repeat new = newIORef (=:) = writeIORef ......
i'm pretty sure that for novices learning Haskell studying these names will be much simpler than studying Monad concepts and so on
Which will eventually handicap them.
Agreed. I would suggest this is no more useful than f . g = g f or the like. /g

On Mon, Nov 13, 2006 at 02:02:36AM -0800, John Meacham wrote:
On Mon, Nov 13, 2006 at 02:27:12PM +1100, Donald Bruce Stewart wrote:
I'm we're going to use this forever more, then a name more meaningful than repeatM_ might be appropriate (personally, I have to check every time whether it is replicate or repeat that is :: Int -> a -> [a]).
now it will be three times easier to remember, as you only need to remember what one of repeat, repeatM, and repeatM_ do to easily determine what the other two do. standard naming conventions are very nice when they fit so well, as they do in this case.
I'm not so sure. The only connection between repeatM_ and lists would be the near-useless repeatM.

I think that both repeatM and repeatM_ should be added for the following reasons. 1. sequence . repeat and sequence_ . repeat are the only specifications that will ever be meant by the names repeatM and repeatM_ (in Control.Monad), so there is no concern for conflict or confusing with these names. 2. the implemention are exteremely short, so there is negligable harm in including them in distributions. 3. repeatM seems plausibly useful in at least the reader monad, and probably others. That being said, I also think it is a fine idea to add the forever function. Haskell thrives on multiple ways of doing the same thing. Giving users reasonable set of options is a good thing. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Mon, 13 Nov 2006, Donald Bruce Stewart wrote:
I would personally rather see repeatM and repeatM_ like the replicateM/replicateM_ pair already in Control.Monad.
I implement them like this: repeatM = sequence . repeat repeatM_ = sequence_ . repeat
Google CodeSearch tells me it's the way replicateM was implemented too: http://www.google.com/codesearch?hl=en&lr=&q=replicateM+file%3A%5C.hs% 24&btnG=Search
Btw, i hope it is ok to give my opinion on this. Im asking since im not a library developer or anything just a normal programmer.
On this topic, we can go back to: http://www.mail-archive.com/cvs-all@haskell.org/msg26511.html
However, it was pointed out that repeatM is next to useless, and it is traditional to use 'forever' for repeatM_ (see for example "Tackling the Awkward Squad", and http://haskell.org/haskellwiki/Roll_your_own_IRC_bot
That being said, repeatM_ isn't too bad, should people prefer it.
I prefer repeatM_ in analogy to List.repeat.

Hello Mattias, Monday, November 13, 2006, 5:51:23 AM, you wrote:
Btw, i hope it is ok to give my opinion on this. Im asking since im not a library developer or anything just a normal programmer.
.. and you think that this list is for crazies only? :D -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Just a remark, not necessarily an objection. Don wrote:
forever' act@ repeats the action infinitely. +forever :: (Monad m) => m a -> m () +forever a = a >> forever a
This forever operation is definable for any (Applicative m), not just (Monad m). Of course, there are plenty of other operators in the library whose types are restrictive in the same way. There's clearly a pragmatic issue here. As it is not currently the case that a Monad instance automatically yields an Applicative instance, it may be more convenient in the short term to stick with the more restrictive version here and generalise later, if ever it becomes pain-free to do so. Cheers Conor

dons:
http://hackage.haskell.org/trac/ghc/ticket/997
Add Kleisli composition to Control.Monad.
Kleisli composition of monads is a foundational feature missing from the current Control.Monad library. A recent discussion revealed solid support for its inclusion.
This patch adds:
(>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :) -- Don

dons@cse.unsw.edu.au (Donald Bruce Stewart) wrote:
Add Kleisli composition to Control.Monad.
(>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :)
No. :-) I've never used them, nor wanted to, so I have no opinion. I can see the nice compositional pattern they embody though. Regards, Malcolm

On Mon, 13 Nov 2006, Malcolm Wallace wrote:
dons@cse.unsw.edu.au (Donald Bruce Stewart) wrote:
Add Kleisli composition to Control.Monad.
(>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :)
No. :-) I've never used them, nor wanted to, so I have no opinion. I can see the nice compositional pattern they embody though.
Strange, the first time, I used them, was processing HTML data parsed by HaXML. :-)

Henning Thielemann
Add Kleisli composition to Control.Monad.
(>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :)
No. :-) I've never used them, nor wanted to, so I have no opinion. I can see the nice compositional pattern they embody though.
Strange, the first time, I used them, was processing HTML data parsed by HaXML. :-)
Oops, egg-on-face time. I had forgotten about that. Yes, the HaXml combinators use Kleisli composition extensively (although it is called `o` there. And I only recognised that ContentFilter is a monad *very* recently.) Regards, Malcolm

On 11/13/06, Donald Bruce Stewart
(>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :)
I want them. See my timeout patch for a case where I wanted one of
these and didn't have it (the catch filter expression).
--
Taral

On 11/13/06, Taral
On 11/13/06, Donald Bruce Stewart
wrote: (>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :)
I want them. See my timeout patch for a case where I wanted one of these and didn't have it (the catch filter expression).
Actually, my tests indicate that (>>>) and (<<<) can be used for any
Monad. So are we defining these again?
--
Taral

taralx:
On 11/13/06, Taral
wrote: On 11/13/06, Donald Bruce Stewart
wrote: (>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :)
I want them. See my timeout patch for a case where I wanted one of these and didn't have it (the catch filter expression).
Actually, my tests indicate that (>>>) and (<<<) can be used for any Monad. So are we defining these again?
Do you mean that we should just import Control.Arrow and use that? Something like: import Control.Arrow main :: IO () main = (x >>> y) 7 x :: Integer -> IO () x = print y :: a -> IO () y = const (return ()) -- Don

On 11/14/06, Taral
On 11/13/06, Donald Bruce Stewart
wrote: Do you mean that we should just import Control.Arrow and use that?
Why not?
Well, it doesn't do the same thing, for starters...

Taral wrote:
Actually, my tests indicate that (>>>) and (<<<) can be used for any Monad. So are we defining these again?
Yes, the Kleisli type "Kleisli a b = a -> m b" is an Arrow. No, it's not the same, since "a -> m b" is not an Arrow on a and b (it's not of the form "arrow a b"). -- Ashley Yakeley

On 11/13/06, Ashley Yakeley
Yes, the Kleisli type "Kleisli a b = a -> m b" is an Arrow. No, it's not the same, since "a -> m b" is not an Arrow on a and b (it's not of the form "arrow a b").
Apparently the type is transparent, though...
Prelude Control.Arrow Control.Monad> :t (return 4) >>> flip replicateM
(return ())
(return 4) >>> flip replicateM (return ()) :: (Monad m) => b -> m [()]
--
Taral

dons:
http://hackage.haskell.org/trac/ghc/ticket/997
Add Kleisli composition to Control.Monad.
Kleisli composition of monads is a foundational feature missing from the current Control.Monad library. A recent discussion revealed solid support for its inclusion.
This patch adds:
(>=>) :: (Monad m) => (a -> m b) -> (b -> m c) -> (a -> m c) (<=<) :: (Monad m) => (b -> m c) -> (a -> m b) -> (a -> m c)
Does anyone have an opinion about these guys? :)
Wee need the functions, no matter which names. That said, I still like (=>>=) and (=<<=) better, but I'm not strongly opposed to the proposed names --- it's just that they sort of look like they might be more closely related with Ord than with Monad. Wolfram

Donald Bruce Stewart wrote:
forever :: (Monad m) => m a -> m ()
This should be: forever :: (Monad m) => m a -> m b I agree with Conor both that this should really be in Applicative and also that it may be more convenient to keep it in Monad for the time being. If "Joined-Up Classes" http://hackage.haskell.org/trac/haskell-prime/ticket/113 is approved, 'forever' would then be one of the values to be generalised to Applicative. -- Ashley Yakeley

On Mon, 13 Nov 2006, Ashley Yakeley wrote:
Donald Bruce Stewart wrote:
forever :: (Monad m) => m a -> m ()
This should be:
forever :: (Monad m) => m a -> m b
forever even has a different type than repeatM_. More reason to have both. -- Russell O'Connor http://r6.ca/ ``All talk about `theft,''' the general counsel of the American Graphophone Company wrote, ``is the merest claptrap, for there exists no property in ideas musical, literary or artistic, except as defined by statute.''

On Mon, Nov 13, 2006 at 04:57:30PM -0500, roconnor@theorem.ca wrote:
On Mon, 13 Nov 2006, Ashley Yakeley wrote:
Donald Bruce Stewart wrote:
forever :: (Monad m) => m a -> m ()
This should be:
forever :: (Monad m) => m a -> m b
forever even has a different type than repeatM_. More reason to have both.
Is anyone else feeling uncomfortably crowded by the current namespace exported by the haskell libraries? I think this is something we need to start keeping in mind. The recent additions to Monoid ate up a whole swath of useful terms for instance, making me have to change all my imports for the most part. If every library followed suit then the import list at the top of modules will become quite convoluted. Short useful names are good, but so is getting at the base functionality of something without wading through a lot of esoteric combinators. John -- John Meacham - ⑆repetae.net⑆john⑈

forever even has a different type than repeatM_. More reason to have both.
Is anyone else feeling uncomfortably crowded by the current namespace exported by the haskell libraries?
I think a good naming criteria is "could anyone have a function defined with this name which _didn't_ do exactly what this one does". For example, repeatM_ - can anyone think of an alternative definition which didn't do the obvious thing? However forever could have loads of interpretations. Thanks Neil

On Mon, Nov 13, 2006 at 01:29:44PM -0800, Ashley Yakeley wrote:
Donald Bruce Stewart wrote:
forever :: (Monad m) => m a -> m ()
This should be:
forever :: (Monad m) => m a -> m b
I agree with Conor both that this should really be in Applicative and also that it may be more convenient to keep it in Monad for the time being. If "Joined-Up Classes" http://hackage.haskell.org/trac/haskell-prime/ticket/113 is approved, 'forever' would then be one of the values to be generalised to Applicative.
if forever is made a part of applicative, it should be made part of the class. It suffers from the same problem as the current broken many and many1 in applicative, since they use implicit recursion, they are useless for anything wanting to do anything but execute them in a monadic framework. i.e., pretty much exactly the sort of things that applicative was made to support (irony?) :) John -- John Meacham - ⑆repetae.net⑆john⑈
participants (16)
-
Aaron Denney
-
Ashley Yakeley
-
Bulat Ziganshin
-
Conor McBride
-
dons@cse.unsw.edu.au
-
Henning Thielemann
-
J. Garrett Morris
-
John Meacham
-
kahl@cas.mcmaster.ca
-
Malcolm Wallace
-
Mattias Bengtsson
-
Neil Mitchell
-
roconnor@theorem.ca
-
Ross Paterson
-
Samuel Bronson
-
Taral