Adding an ignore function to Control.Monad

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 So while writing my wp-archivebot, I ran into the issue that forkIO requires IO () but returns IO ThreadId, and that many useful IO functions will return IO a instead of IO (). This forces some awkward contortions. Suppose I want to ping the WebCite website at a particular address, and this request makes WebCite archive a URL embedded in that address. Presumably I could venture into the depths of Network.HTTP to figure out how to ping an URL without also pulling down the server's HTML, but why do that when I already have obviously 'openURL :: String -> IO String'? Much easier to do something like 'openURL "webcite.org" ++ foo ++ "other stuff" '. But my bot needs to handle quite a few URLs; one at a time, what with all the waits and timeouts, isn't going to hack it. So for a given link, I forkIO the openURL request. But of course, forkIO demands IO (), so I toss in a '>> return ()'. Fair enough. So I examine the performance, and it's still too slow. Recent Changes has hundreds of different pages a minute. I'd better fork each page (and then fork for each link). But wait, all those forkIOs are returning IO ThreadIds, and my top-level forkIO call demands IO ()... So another >> return (). At this point, the code is starting to look pretty silly - something like '...stuff >> return ()) >> return ())'. So I see the repeated pattern, and by the rule of 3, factor it out to: - -- | Convenience function. 'forkIO' and 'forM_' demand return types of 'IO ()', but most interesting - -- IO functions don't return void. So one adds a call to 'return ()'; this just factors it out. ignore ∷ (Monad m) ⇒ m a → m () ignore x = x >> return () Not the most complex convenience function I've ever written, but not any simpler than, say Control.Monad.forever or for that matter, most of the stuff in Control.Monad. I'd think it'd be useful for more than just me. Agda is lousy with calls to '>> return ()'; and then there's ZMachine, arrayref, whim, the barracuda packages, binary, bnfc, buddha, bytestring, c2hs, cabal, chesslibrary, comas, conjure, curl, darcs, darcs-benchmark, dbus-haskell, ddc, dephd, derive, dhs, drift, easyvision, ehc, filestore, folkung, geni, geordi, gtk2hs, gnuplot, ginsu, halfs, happstack, haskeline, hback, hbeat... You get the picture. I realize the specific name of 'ignore' can be bikeshedded to death, but it's clear, it's short, Hoogle turns up one other function with ignore in its name (Distribution.ParseUtils ignoreUnrec), and it's been independently named 'ignore' by another Haskeller (lilac). Existing uses of the string 'ignore are rare - it's in a few places as a variable, cabal and cabal-install and ehc and tar have where definitions of an ignore, a test for directory defines an ignore and imports Control.Monad unqualified, fit defines an 'ignore' but doesn't seem to use it in any module that also imports Control.Monad unqualified, halipeto defines an ignore but doesn't import Control.Monad, shim/yi has a let definition of an ignore, yhc has a where definition of an ignore. And that's about it. One of directory's tests would break, and the rest might have an additional -Wall warning. - -- gwern -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux) iEYEAREKAAYFAkov5Q0ACgkQvpDo5Pfl1oIsRQCghUqynThzcT+OYV1KaYJhGFhv 6yYAnjf7CVOm0+Fg1FBa9IpdVIrRpCZm =Cd8V -----END PGP SIGNATURE-----

+1.
I also remember this post by Neil Mitchell which seems appropriate:
http://neilmitchell.blogspot.com/2008/12/mapm-mapm-and-monadic-statements.ht....
He also uses the name "ignore" for your function.
Michael
On Wed, Jun 10, 2009 at 7:53 PM, Gwern Branwen
-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512
So while writing my wp-archivebot, I ran into the issue that forkIO requires IO () but returns IO ThreadId, and that many useful IO functions will return IO a instead of IO ().
This forces some awkward contortions. Suppose I want to ping the WebCite website at a particular address, and this request makes WebCite archive a URL embedded in that address. Presumably I could venture into the depths of Network.HTTP to figure out how to ping an URL without also pulling down the server's HTML, but why do that when I already have obviously 'openURL :: String -> IO String'? Much easier to do something like 'openURL "webcite.org" ++ foo ++ "other stuff" '.
But my bot needs to handle quite a few URLs; one at a time, what with all the waits and timeouts, isn't going to hack it. So for a given link, I forkIO the openURL request. But of course, forkIO demands IO (), so I toss in a '>> return ()'. Fair enough.
So I examine the performance, and it's still too slow. Recent Changes has hundreds of different pages a minute. I'd better fork each page (and then fork for each link). But wait, all those forkIOs are returning IO ThreadIds, and my top-level forkIO call demands IO ()... So another >> return (). At this point, the code is starting to look pretty silly - something like '...stuff >> return ()) >> return ())'.
So I see the repeated pattern, and by the rule of 3, factor it out to:
- -- | Convenience function. 'forkIO' and 'forM_' demand return types of 'IO ()', but most interesting - -- IO functions don't return void. So one adds a call to 'return ()'; this just factors it out. ignore ∷ (Monad m) ⇒ m a → m () ignore x = x >> return ()
Not the most complex convenience function I've ever written, but not any simpler than, say Control.Monad.forever or for that matter, most of the stuff in Control.Monad.
I'd think it'd be useful for more than just me. Agda is lousy with calls to '>> return ()'; and then there's ZMachine, arrayref, whim, the barracuda packages, binary, bnfc, buddha, bytestring, c2hs, cabal, chesslibrary, comas, conjure, curl, darcs, darcs-benchmark, dbus-haskell, ddc, dephd, derive, dhs, drift, easyvision, ehc, filestore, folkung, geni, geordi, gtk2hs, gnuplot, ginsu, halfs, happstack, haskeline, hback, hbeat... You get the picture.
I realize the specific name of 'ignore' can be bikeshedded to death, but it's clear, it's short, Hoogle turns up one other function with ignore in its name (Distribution.ParseUtils ignoreUnrec), and it's been independently named 'ignore' by another Haskeller (lilac).
Existing uses of the string 'ignore are rare - it's in a few places as a variable, cabal and cabal-install and ehc and tar have where definitions of an ignore, a test for directory defines an ignore and imports Control.Monad unqualified, fit defines an 'ignore' but doesn't seem to use it in any module that also imports Control.Monad unqualified, halipeto defines an ignore but doesn't import Control.Monad, shim/yi has a let definition of an ignore, yhc has a where definition of an ignore. And that's about it. One of directory's tests would break, and the rest might have an additional -Wall warning.
- -- gwern -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux)
iEYEAREKAAYFAkov5Q0ACgkQvpDo5Pfl1oIsRQCghUqynThzcT+OYV1KaYJhGFhv 6yYAnjf7CVOm0+Fg1FBa9IpdVIrRpCZm =Cd8V -----END PGP SIGNATURE----- _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I've used this same function with parser combinators as well. I would prefer
a version that just relied on the fact that you have a Functor however, so
you can use it with Applicatives or any other Functor you happen to have
lying around.
ignore :: Functor f => f a -> f ()
ignore = fmap (const ())
On Wed, Jun 10, 2009 at 12:56 PM, Michael Snoyman
+1.
I also remember this post by Neil Mitchell which seems appropriate: http://neilmitchell.blogspot.com/2008/12/mapm-mapm-and-monadic-statements.ht.... He also uses the name "ignore" for your function.
Michael
On Wed, Jun 10, 2009 at 7:53 PM, Gwern Branwen
wrote: -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512
So while writing my wp-archivebot, I ran into the issue that forkIO requires IO () but returns IO ThreadId, and that many useful IO functions will return IO a instead of IO ().
This forces some awkward contortions. Suppose I want to ping the WebCite website at a particular address, and this request makes WebCite archive a URL embedded in that address. Presumably I could venture into the depths of Network.HTTP to figure out how to ping an URL without also pulling down the server's HTML, but why do that when I already have obviously 'openURL :: String -> IO String'? Much easier to do something like 'openURL "webcite.org" ++ foo ++ "other stuff" '.
But my bot needs to handle quite a few URLs; one at a time, what with all the waits and timeouts, isn't going to hack it. So for a given link, I forkIO the openURL request. But of course, forkIO demands IO (), so I toss in a '>> return ()'. Fair enough.
So I examine the performance, and it's still too slow. Recent Changes has hundreds of different pages a minute. I'd better fork each page (and then fork for each link). But wait, all those forkIOs are returning IO ThreadIds, and my top-level forkIO call demands IO ()... So another >> return (). At this point, the code is starting to look pretty silly - something like '...stuff >> return ()) >> return ())'.
So I see the repeated pattern, and by the rule of 3, factor it out to:
- -- | Convenience function. 'forkIO' and 'forM_' demand return types of 'IO ()', but most interesting - -- IO functions don't return void. So one adds a call to 'return ()'; this just factors it out. ignore ∷ (Monad m) ⇒ m a → m () ignore x = x >> return ()
Not the most complex convenience function I've ever written, but not any simpler than, say Control.Monad.forever or for that matter, most of the stuff in Control.Monad.
I'd think it'd be useful for more than just me. Agda is lousy with calls to '>> return ()'; and then there's ZMachine, arrayref, whim, the barracuda packages, binary, bnfc, buddha, bytestring, c2hs, cabal, chesslibrary, comas, conjure, curl, darcs, darcs-benchmark, dbus-haskell, ddc, dephd, derive, dhs, drift, easyvision, ehc, filestore, folkung, geni, geordi, gtk2hs, gnuplot, ginsu, halfs, happstack, haskeline, hback, hbeat... You get the picture.
I realize the specific name of 'ignore' can be bikeshedded to death, but it's clear, it's short, Hoogle turns up one other function with ignore in its name (Distribution.ParseUtils ignoreUnrec), and it's been independently named 'ignore' by another Haskeller (lilac).
Existing uses of the string 'ignore are rare - it's in a few places as a variable, cabal and cabal-install and ehc and tar have where definitions of an ignore, a test for directory defines an ignore and imports Control.Monad unqualified, fit defines an 'ignore' but doesn't seem to use it in any module that also imports Control.Monad unqualified, halipeto defines an ignore but doesn't import Control.Monad, shim/yi has a let definition of an ignore, yhc has a where definition of an ignore. And that's about it. One of directory's tests would break, and the rest might have an additional -Wall warning.
- -- gwern -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux)
iEYEAREKAAYFAkov5Q0ACgkQvpDo5Pfl1oIsRQCghUqynThzcT+OYV1KaYJhGFhv 6yYAnjf7CVOm0+Fg1FBa9IpdVIrRpCZm =Cd8V -----END PGP SIGNATURE----- _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I asked for something like that some time ago, and was also given this sugestion. So, it seems to be usefull to many: http://www.mail-archive.com/haskell-cafe@haskell.org/msg52627.html Best, Maurício
I've used this same function with parser combinators as well. I would prefer a version that just relied on the fact that you have a Functor however, so you can use it with Applicatives or any other Functor you happen to have lying around.
ignore :: Functor f => f a -> f () ignore = fmap (const ())
On Wed, Jun 10, 2009 at 12:56 PM, Michael Snoyman
mailto:michael@snoyman.com> wrote: +1.
I also remember this post by Neil Mitchell which seems appropriate: http://neilmitchell.blogspot.com/2008/12/mapm-mapm-and-monadic-statements.ht.... He also uses the name "ignore" for your function.
Michael
On Wed, Jun 10, 2009 at 7:53 PM, Gwern Branwen
mailto:gwern0@gmail.com> wrote: -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512
So while writing my wp-archivebot, I ran into the issue that forkIO requires IO () but returns IO ThreadId, and that many useful IO functions will return IO a instead of IO ().
This forces some awkward contortions. Suppose I want to ping the WebCite website at a particular address, and this request makes WebCite archive a URL embedded in that address. Presumably I could venture into the depths of Network.HTTP to figure out how to ping an URL without also pulling down the server's HTML, but why do that when I already have obviously 'openURL :: String -> IO String'? Much easier to do something like 'openURL "webcite.org http://webcite.org/" ++ foo ++ "other stuff" '.
But my bot needs to handle quite a few URLs; one at a time, what with all the waits and timeouts, isn't going to hack it. So for a given link, I forkIO the openURL request. But of course, forkIO demands IO (), so I toss in a '>> return ()'. Fair enough.
So I examine the performance, and it's still too slow. Recent Changes has hundreds of different pages a minute. I'd better fork each page (and then fork for each link). But wait, all those forkIOs are returning IO ThreadIds, and my top-level forkIO call demands IO ()... So another >> return (). At this point, the code is starting to look pretty silly - something like '...stuff >> return ()) >> return ())'.
So I see the repeated pattern, and by the rule of 3, factor it out to:
- -- | Convenience function. 'forkIO' and 'forM_' demand return types of 'IO ()', but most interesting - -- IO functions don't return void. So one adds a call to 'return ()'; this just factors it out. ignore ∷ (Monad m) ⇒ m a → m () ignore x = x >> return ()
Not the most complex convenience function I've ever written, but not any simpler than, say Control.Monad.forever or for that matter, most of the stuff in Control.Monad.
I'd think it'd be useful for more than just me. Agda is lousy with calls to '>> return ()'; and then there's ZMachine, arrayref, whim, the barracuda packages, binary, bnfc, buddha, bytestring, c2hs, cabal, chesslibrary, comas, conjure, curl, darcs, darcs-benchmark, dbus-haskell, ddc, dephd, derive, dhs, drift, easyvision, ehc, filestore, folkung, geni, geordi, gtk2hs, gnuplot, ginsu, halfs, happstack, haskeline, hback, hbeat... You get the picture.
I realize the specific name of 'ignore' can be bikeshedded to death, but it's clear, it's short, Hoogle turns up one other function with ignore in its name (Distribution.ParseUtils ignoreUnrec), and it's been independently named 'ignore' by another Haskeller (lilac).
Existing uses of the string 'ignore are rare - it's in a few places as a variable, cabal and cabal-install and ehc and tar have where definitions of an ignore, a test for directory defines an ignore and imports Control.Monad unqualified, fit defines an 'ignore' but doesn't seem to use it in any module that also imports Control.Monad unqualified, halipeto defines an ignore but doesn't import Control.Monad, shim/yi has a let definition of an ignore, yhc has a where definition of an ignore. And that's about it. One of directory's tests would break, and the rest might have an additional -Wall warning.
- -- gwern -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux)
iEYEAREKAAYFAkov5Q0ACgkQvpDo5Pfl1oIsRQCghUqynThzcT+OYV1KaYJhGFhv 6yYAnjf7CVOm0+Fg1FBa9IpdVIrRpCZm =Cd8V -----END PGP SIGNATURE----- _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
------------------------------------------------------------------------
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 On Wed, Jun 10, 2009 at 1:44 PM, Maurício wrote:
I asked for something like that some time ago, and was also given this sugestion. So, it seems to be usefull to many:
http://www.mail-archive.com/haskell-cafe@haskell.org/msg52627.html
Best, Maurício
OK, so all the response seems positive. I've opened up a ticket: http://hackage.haskell.org/trac/ghc/ticket/3292 (I'm using Edward's Functor version, because it works just as well as the monadic one, and I see no reason to mess with people who'd like to use it for Functor or Applicative.) - -- gwern -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux) iEYEAREKAAYFAkowA58ACgkQvpDo5Pfl1oL2JQCdGyiSAJs37uSxTb6t4hrR1kyL mdYAnigoIywjw97lXbEPJZWgQwZU26nz =s2Dq -----END PGP SIGNATURE-----

On the other hand, maybe it's also an argument to change all the functions like forkIO from :: IO () -> IO ThreadID to :: IO a -> IO ThreadID I mean, surely they don't rely on the value of a () return-type, other than to pass on to other places that artificially require the ()-type? okay, a hypothetical function twice :: IO () -> IO () twice a = a >> a would really need not to return the second result arbitrarily (as it would have to with a mere type-change, to "IO a -> IO a"), so it could be twice :: IO a -> IO () twice a = ignore (a >> a) Isaac Dupree wrote:
+1, I also invented that ignore function with that name.

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 On Wed, Jun 10, 2009 at 1:13 PM, Isaac Dupree wrote:
On the other hand, maybe it's also an argument to change all the functions like forkIO from :: IO () -> IO ThreadID to :: IO a -> IO ThreadID
I mean, surely they don't rely on the value of a () return-type, other than to pass on to other places that artificially require the ()-type?
okay, a hypothetical function twice :: IO () -> IO () twice a = a >> a would really need not to return the second result arbitrarily (as it would have to with a mere type-change, to "IO a -> IO a"), so it could be twice :: IO a -> IO () twice a = ignore (a >> a)
I think generalizing forkIO is a great idea; but I wanted to do one change at a time. Keep the discussion on just 'ignore', and only moot about a forkIO change when 'ignore' is finished up. - -- gwern -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux) iEYEAREKAAYFAkowA+QACgkQvpDo5Pfl1oI0fQCeJcuHxWD8M9f5ZkAB6egfrZWI FE4An1GspyC3jENzZ8Vvr6FUsurMgSJd =QmIu -----END PGP SIGNATURE-----

Isaac Dupree schrieb:
On the other hand, maybe it's also an argument to change all the functions like forkIO from :: IO () -> IO ThreadID to :: IO a -> IO ThreadID
I mean, surely they don't rely on the value of a () return-type, other than to pass on to other places that artificially require the ()-type?
No, I think it is already bad enough, that (>>) has type (m a -> m b -> m b) instead of (m () -> m b -> m b). It is like automatically ignoring return values in C. It is too easy to ignore a result that is important.

Henning Thielemann
On the other hand, maybe it's also an argument to change all the functions like forkIO to (:: IO a -> IO ThreadID)
No, I think it is already bad enough, that (>>) has type (m a -> m b -> m b) instead of (m () -> m b -> m b). It is like automatically ignoring return values in C. It is too easy to ignore a result that is important.
Exactly what I was going to say. I think "ignore" is fine as a kludge-around, and I'm definitely +1 for it. However, if I want to ignore the result of, say, getLine, it's easy enough to write (getLine >>= \_ -> ...), which makes it clear that I meant to do that.

Alright, I see that there haven't been any real complaints about adding Control.Monad.ignore since I first posted on 10 June. (Although there was a lot of related-but-off-topic discussion.) Since then, Don Stewart has pointed out http://hackage.haskell.org/trac/ghc/ticket/3292 that there is a very similar function specified in the FFI standard http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html#x8-350005.10 - 'void :: IO a -> IO ()'. I don't favor 'ignore' over 'void' to an extent significant enough to make that an issue. But it's no longer clear what to do. Do we move void with its current type to Control.Monad and have Foreign.Marshal.Error re-export it? Do we define void with the generalized Functor sig, and have F.M.E re-export with a restricted type sig? Do we simply use my ignore patch and define F.M.E.void = ignore (with the restricted type sig)? The specifics of what to do are unclear enough that I don't think there's consensus for what to do with void, even if we clearly want some sort of void/ignore in Control.Monad. -- gwern

Gwern Branwen wrote:
Since then, Don Stewart has pointed out http://hackage.haskell.org/trac/ghc/ticket/3292 that there is a very similar function specified in the FFI standard http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html#x8-350005.10 - 'void :: IO a -> IO ()'.
Are we willing to change (generalize) the type of Foreign.Marshal.Error.void? If so, we could export (void :: Functor m => m a -> m ()) from both Control.Monad and F.M.E (if we wanted to). If we're not willing, then I think it would be a bit more convenient to name them different things (so that if you import both modules you don't get a name-conflict for using 'void'). I vote to just name it Control.Monad.ignore . Many people independently invented the name "ignore" in their own projects. Also I suspect the name "void" in FFI has some etymology in C's equivalent, casting expressions to void (eg: (void)printf(something); ) which I doubt most haskell coders care about most of the time? -Isaac

void is the wrong name, wrong type, wrong purpose and wrong module. We
could fix all those things, but I think we should just add ignore as
previously agreed (+1 for that)
Thanks, Neil
On Thu, Jul 2, 2009 at 4:11 AM, Isaac
Dupree
Gwern Branwen wrote:
Since then, Don Stewart has pointed out http://hackage.haskell.org/trac/ghc/ticket/3292 that there is a very similar function specified in the FFI standard http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html#x8-350005.10 - 'void :: IO a -> IO ()'.
Are we willing to change (generalize) the type of Foreign.Marshal.Error.void? If so, we could export (void :: Functor m => m a -> m ()) from both Control.Monad and F.M.E (if we wanted to). If we're not willing, then I think it would be a bit more convenient to name them different things (so that if you import both modules you don't get a name-conflict for using 'void').
I vote to just name it Control.Monad.ignore . Many people independently invented the name "ignore" in their own projects. Also I suspect the name "void" in FFI has some etymology in C's equivalent, casting expressions to void (eg: (void)printf(something); ) which I doubt most haskell coders care about most of the time?
-Isaac _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I agree with Neil on all those points. F.M.E.void has too many things to fix
to bring it inline with ignore in one go and a worse name.
+1 on adding ignore though.
-Edward Kmett
On Thu, Jul 2, 2009 at 2:26 AM, Neil Mitchell
void is the wrong name, wrong type, wrong purpose and wrong module. We could fix all those things, but I think we should just add ignore as previously agreed (+1 for that)
Thanks, Neil
On Thu, Jul 2, 2009 at 4:11 AM, Isaac Dupree
wrote: Gwern Branwen wrote:
Since then, Don Stewart has pointed out http://hackage.haskell.org/trac/ghc/ticket/3292 that there is a very similar function specified in the FFI standard
http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html#x8-350005.10
- 'void :: IO a -> IO ()'.
Are we willing to change (generalize) the type of Foreign.Marshal.Error.void? If so, we could export (void :: Functor m => m a -> m ()) from both Control.Monad and F.M.E (if we wanted to). If we're not willing, then I think it would be a bit more convenient to name them different things (so that if you import both modules you don't get a name-conflict for using 'void').
I vote to just name it Control.Monad.ignore . Many people independently invented the name "ignore" in their own projects. Also I suspect the name "void" in FFI has some etymology in C's equivalent, casting expressions to void (eg: (void)printf(something); ) which I doubt most haskell coders care about most of the time?
-Isaac _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I for one don't like 'ignore' -- it implies to me somehow that the argument itself is ignored, rather than the result after evaluation. Also, 'void' already exists, and is part of a decade-old FFI standard. -- Don ekmett:
I agree with Neil on all those points. F.M.E.void has too many things to fix to bring it inline with ignore in one go and a worse name.
+1 on adding ignore though.
-Edward Kmett
On Thu, Jul 2, 2009 at 2:26 AM, Neil Mitchell
wrote: void is the wrong name, wrong type, wrong purpose and wrong module. We could fix all those things, but I think we should just add ignore as previously agreed (+1 for that)
Thanks, Neil
On Thu, Jul 2, 2009 at 4:11 AM, Isaac Dupree
wrote: > Gwern Branwen wrote: >> >> Since then, Don Stewart has pointed out >> http://hackage.haskell.org/trac/ghc/ticket/3292 that there is a very >> similar function specified in the FFI standard >> http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html# x8-350005.10 >> - 'void :: IO a -> IO ()'. > > Are we willing to change (generalize) the type of > Foreign.Marshal.Error.void? If so, we could export (void :: Functor m => m > a -> m ()) from both Control.Monad and F.M.E (if we wanted to). If we're > not willing, then I think it would be a bit more convenient to name them > different things (so that if you import both modules you don't get a > name-conflict for using 'void'). > > I vote to just name it Control.Monad.ignore . Many people independently > invented the name "ignore" in their own projects. Also I suspect the name > "void" in FFI has some etymology in C's equivalent, casting expressions to > void (eg: (void)printf(something); ) which I doubt most haskell coders care > about most of the time? > > -Isaac > _______________________________________________ > Libraries mailing list > Libraries@haskell.org > http://www.haskell.org/mailman/listinfo/libraries > _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hi,
I am not convinced that we need this function in the standard
libraries but if people find it useful, then I agree with Don's point
that we should stick with "void" because I think that:
void readLine
read better then
ignore readLine
-Iavor
PS: How about devNull = return ()? Then readLine >> devNull would
make sense! :p
On Thu, Jul 2, 2009 at 10:22 AM, Don Stewart
I for one don't like 'ignore' -- it implies to me somehow that the argument itself is ignored, rather than the result after evaluation.
Also, 'void' already exists, and is part of a decade-old FFI standard.
-- Don
ekmett:
I agree with Neil on all those points. F.M.E.void has too many things to fix to bring it inline with ignore in one go and a worse name.
+1 on adding ignore though.
-Edward Kmett
On Thu, Jul 2, 2009 at 2:26 AM, Neil Mitchell
wrote: void is the wrong name, wrong type, wrong purpose and wrong module. We could fix all those things, but I think we should just add ignore as previously agreed (+1 for that)
Thanks, Neil
On Thu, Jul 2, 2009 at 4:11 AM, Isaac Dupree
wrote: > Gwern Branwen wrote: >> >> Since then, Don Stewart has pointed out >> http://hackage.haskell.org/trac/ghc/ticket/3292 that there is a very >> similar function specified in the FFI standard >> http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html# x8-350005.10 >> - 'void :: IO a -> IO ()'. > > Are we willing to change (generalize) the type of > Foreign.Marshal.Error.void? If so, we could export (void :: Functor m => m > a -> m ()) from both Control.Monad and F.M.E (if we wanted to). If we're > not willing, then I think it would be a bit more convenient to name them > different things (so that if you import both modules you don't get a > name-conflict for using 'void'). > > I vote to just name it Control.Monad.ignore . Many people independently > invented the name "ignore" in their own projects. Also I suspect the name > "void" in FFI has some etymology in C's equivalent, casting expressions to > void (eg: (void)printf(something); ) which I doubt most haskell coders care > about most of the time? > > -Isaac > _______________________________________________ > Libraries mailing list > Libraries@haskell.org > http://www.haskell.org/mailman/listinfo/libraries > _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

OK, let's apply a little democracy here. Reading back through the thread, I tally the votes: # Nothing David Menendez John Meachem (?) # Just ## Control.Monad.ignore m a -> m () Michael Snoyman Neil Mitchell Isaac Dupree Maurício Martijn van Steenbergen ### Control.Monad.ignore f a -> f () Edward Kmett ## Control.Monad.void m a -> m () Don Stewart Iavor Diatchki -- gwern

gwern0:
OK, let's apply a little democracy here. Reading back through the thread, I tally the votes:
# Nothing David Menendez John Meachem (?)
# Just ## Control.Monad.ignore m a -> m () Michael Snoyman Neil Mitchell Isaac Dupree Maurício Martijn van Steenbergen
### Control.Monad.ignore f a -> f () Edward Kmett
## Control.Monad.void m a -> m () Don Stewart Iavor Diatchki
That's an odd mix too. I wonder if we even reached quorum. -- Don

I'm not opposed to using void instead of ignore. Out of curiosity, is anyone
interested in having the Functor version of void? I'm not sure I see a
reason to unnecessarily limit ourselves to Monads here.
Also, if we do end up using void, what's going to happen with the FFI copy?
Michael
On Sat, Jul 11, 2009 at 6:10 AM, Don Stewart
gwern0:
OK, let's apply a little democracy here. Reading back through the thread, I tally the votes:
# Nothing David Menendez John Meachem (?)
# Just ## Control.Monad.ignore m a -> m () Michael Snoyman Neil Mitchell Isaac Dupree Maurício Martijn van Steenbergen
### Control.Monad.ignore f a -> f () Edward Kmett
## Control.Monad.void m a -> m () Don Stewart Iavor Diatchki
That's an odd mix too. I wonder if we even reached quorum.
-- Don _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Excerpts from Michael Snoyman's message of Sat Jul 11 22:03:49 +0200 2009:
I'm not opposed to using void instead of ignore. Out of curiosity, is anyone interested in having the Functor version of void? I'm not sure I see a reason to unnecessarily limit ourselves to Monads here.
+1 to a functor version Moreover I also think void should be related to an empty type. What about 'discard'?
Also, if we do end up using void, what's going to happen with the FFI copy?
Michael
On Sat, Jul 11, 2009 at 6:10 AM, Don Stewart
wrote: gwern0:
OK, let's apply a little democracy here. Reading back through the thread, I tally the votes:
# Nothing David Menendez John Meachem (?)
# Just ## Control.Monad.ignore m a -> m () Michael Snoyman Neil Mitchell Isaac Dupree Maurício Martijn van Steenbergen
### Control.Monad.ignore f a -> f () Edward Kmett
## Control.Monad.void m a -> m () Don Stewart Iavor Diatchki
That's an odd mix too. I wonder if we even reached quorum.
-- Nicolas Pouillard http://nicolaspouillard.fr

Am Sonntag, 12. Juli 2009 11:54 schrieb Nicolas Pouillard:
Excerpts from Michael Snoyman's message of Sat Jul 11 22:03:49 +0200 2009:
I'm not opposed to using void instead of ignore. Out of curiosity, is anyone interested in having the Functor version of void? I'm not sure I see a reason to unnecessarily limit ourselves to Monads here.
+1 to a functor version
+1 The function could be used, for example, as a parser, and parsers are not always monads.
What about 'discard'?
Sounds good. Best wishes, Wolfgang

On Fri, Jul 17, 2009 at 8:43 AM, Wolfgang Jeltsch
Am Sonntag, 12. Juli 2009 11:54 schrieb Nicolas Pouillard:
Excerpts from Michael Snoyman's message of Sat Jul 11 22:03:49 +0200 2009:
I'm not opposed to using void instead of ignore. Out of curiosity, is anyone interested in having the Functor version of void? I'm not sure I see a reason to unnecessarily limit ourselves to Monads here.
+1 to a functor version
+1
The function could be used, for example, as a parser, and parsers are not always monads.
What about 'discard'?
Sounds good.
Best wishes, Wolfgang
Approximately 5 months later, it seems no one has commented on it since. Too bad; it could've made it in in time for GHC 6.12. At this point I'd like to run another poll to see whether consensus has changed. If no one objects beyond what we've already seen, I'm going to submit a 'void :: f a -> f ()' patch as the most universal & general version, and hopefully it will be applied... You'll remember the last one wound up being: # Nothing - David Menendez - Henning Thielemann (?) - John Meachem (?) # Just ## Control.Monad.ignore :: m a -> m () - Isaac Dupree - Martijn van Steenbergen - Maurício - Michael Snoyman - Neil Mitchell ### Control.Monad.ignore:: f a -> f () - Edward Kmett ## Control.Monad.void m a -> m () (or void :: f a -> f ()) - Don Stewart - Iavor Diatchki - Jeff Wheeler - Johann Tibell - Malcolm Wallace - Michael Snoyman (as well) - Nicolas Pouillard - Stephan Friedrichs ## Control.Monad.discard :: f a -> f () - Nicolas Pouillard - Wolfgang Jeltsch -- gwern

2009/12/14 Gwern Branwen
On Fri, Jul 17, 2009 at 8:43 AM, Wolfgang Jeltsch
wrote: Am Sonntag, 12. Juli 2009 11:54 schrieb Nicolas Pouillard:
Excerpts from Michael Snoyman's message of Sat Jul 11 22:03:49 +0200 2009:
I'm not opposed to using void instead of ignore. Out of curiosity, is anyone interested in having the Functor version of void? I'm not sure I see a reason to unnecessarily limit ourselves to Monads here.
+1 to a functor version
+1
The function could be used, for example, as a parser, and parsers are not always monads.
What about 'discard'?
Sounds good.
Best wishes, Wolfgang
Approximately 5 months later, it seems no one has commented on it since. Too bad; it could've made it in in time for GHC 6.12.
At this point I'd like to run another poll to see whether consensus has changed. If no one objects beyond what we've already seen, I'm going to submit a 'void :: f a -> f ()' patch as the most universal & general version, and hopefully it will be applied...
You'll remember the last one wound up being:
# Nothing - David Menendez - Henning Thielemann (?) - John Meachem (?)
# Just ## Control.Monad.ignore :: m a -> m () - Isaac Dupree - Martijn van Steenbergen - Maurício - Michael Snoyman - Neil Mitchell
### Control.Monad.ignore:: f a -> f () - Edward Kmett
## Control.Monad.void m a -> m () (or void :: f a -> f ())
- Don Stewart - Iavor Diatchki - Jeff Wheeler - Johann Tibell - Malcolm Wallace - Michael Snoyman (as well) - Nicolas Pouillard - Stephan Friedrichs
## Control.Monad.discard :: f a -> f () - Nicolas Pouillard - Wolfgang Jeltsch
-- gwern _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
If I may: discard++ -- Deniz Dogan

## Control.Monad.void m a -> m () (or void :: f a -> f ())
By the latter, I take it you mean void :: Functor f => f a -> f () void = fmap (const ()) thereby avoiding any premature restriction to Monad. I would be in favour of the generalisation (and of the name 'void').
## Control.Monad.discard :: f a -> f ()
I vote against 'discard', mainly because I already use it frequently, as an infix operator discard :: Applicative f => f a -> f b -> f a It can be jolly useful to intersperse with the `apply` operator e.g. list item = empty `orElse` fmap (:) `apply` item `discard` satisfy ":" `apply` list Regards, Malcolm

Sorry, I didn't respond to the survey because I liked the idea,
preferring the Functor versions of course, and I'm not fussy about the
name. They'll all do for me. But if you want a vote, I'll jump on
the void bandwagon just to make a deadlock less likely :)
On Mon, Dec 14, 2009 at 8:43 AM, Malcolm Wallace
I vote against 'discard', mainly because I already use it frequently, as an infix operator
discard :: Applicative f => f a -> f b -> f a
Isn't that (<*)?

On Mon, Dec 14, 2009 at 8:43 AM, Malcolm Wallace
wrote: I vote against 'discard', mainly because I already use it frequently, as an infix operator
discard :: Applicative f => f a -> f b -> f a
Isn't that (<*)?
Quite possibly. I find the chosen symbols for Applicative very difficult to remember though, and much prefer textual names. Regards, Malcolm

On Mon, 14 Dec 2009, Gwern Branwen wrote:
You'll remember the last one wound up being:
# Nothing - David Menendez - Henning Thielemann (?) - John Meachem (?)
What does it mean to be in category Nothing? I like the 'ignore' function, the name is not important for me and I prefer the Functor constraint.
# Just ## Control.Monad.ignore :: m a -> m () - Isaac Dupree - Martijn van Steenbergen - Maurício - Michael Snoyman - Neil Mitchell
### Control.Monad.ignore:: f a -> f () - Edward Kmett
## Control.Monad.void m a -> m () (or void :: f a -> f ())
- Don Stewart - Iavor Diatchki - Jeff Wheeler - Johann Tibell - Malcolm Wallace - Michael Snoyman (as well) - Nicolas Pouillard - Stephan Friedrichs
## Control.Monad.discard :: f a -> f () - Nicolas Pouillard - Wolfgang Jeltsch

An update on the poll: # Nothing - David Menendez - John Meachem (?) # Just ## Control.Monad.ignore :: m a -> m () - Isaac Dupree - Martijn van Steenbergen - Maurício - Michael Snoyman - Neil Mitchell ### Control.Monad.ignore:: f a -> f () - Edward Kmett - Henning Thielemann ## Control.Monad.void :: f a -> f () - Don Stewart - Iavor Diatchki - Jeff Wheeler - Johann Tibell - Malcolm Wallace - Michael Snoyman (as well) - Nicolas Pouillard - Stephan Friedrichs - Evan Laforce ## Control.Monad.discard :: f a -> f () - Nicolas Pouillard - Wolfgang Jeltsch - Deniz Dogan I think consensus has been reached to: 1) add X 2) add X :: f a -> () The exact name - whether ignore/void/discard - is not so clear with consensus. So I'm just going to name it 'void' for consistency with Foreign and foreign languages. The patch has been sent here, and has also been attached to the ticket: http://hackage.haskell.org/trac/ghc/ticket/3292 I hope we can finally bring this issue to a close! -- gwern

Gwern Branwen wrote:
## Control.Monad.ignore :: m a -> m () - Isaac Dupree
(for the record, I wanted to generalize it to Functor, maybe you're counting from early in the discussion before that was brought up :-)
I think consensus has been reached to: 1) add X 2) add X :: f a -> ()
The exact name - whether ignore/void/discard - is not so clear with consensus. So I'm just going to name it 'void' for consistency with Foreign and foreign languages.
yay! -Isaac

I'm pleased to note that thanks to Malcolm Wallace, the patch has been pushed: http://hackage.haskell.org/trac/ghc/ticket/3292#comment:7 Y'all can look forward to a 'void' in GHC 6.14, likely. -- gwern

On Fri, 10 Jul 2009, Gwern Branwen wrote:
OK, let's apply a little democracy here. Reading back through the thread, I tally the votes:
This shouldn't really be considered a straight vote, but:
## Control.Monad.ignore m a -> m () ### Control.Monad.ignore f a -> f ()
+1 for either of these options. Ganesh

On Wed, Jul 1, 2009 at 4:45 PM, Gwern Branwen
Alright, I see that there haven't been any real complaints about adding Control.Monad.ignore since I first posted on 10 June. (Although there was a lot of related-but-off-topic discussion.)
I'll complain. I'm still not convinced that we need a name for (>> return ()).
--
Dave Menendez

David Menendez wrote:
On Wed, Jul 1, 2009 at 4:45 PM, Gwern Branwen
wrote: Alright, I see that there haven't been any real complaints about adding Control.Monad.ignore since I first posted on 10 June. (Although there was a lot of related-but-off-topic discussion.)
I'll complain. I'm still not convinced that we need a name for (>> return ()).
I think adding ignore is a good idea. I have several examples where I call a function expecting an M () but the last statement in my argument do-block has type M A. For that alone already I think ignore is valuable idiom. Martijn.
participants (18)
-
Bart Massey
-
David Menendez
-
Deniz Dogan
-
Don Stewart
-
Edward Kmett
-
Evan Laforge
-
Ganesh Sittampalam
-
Gwern Branwen
-
Henning Thielemann
-
Iavor Diatchki
-
Isaac Dupree
-
Malcolm Wallace
-
Martijn van Steenbergen
-
Maurício
-
Michael Snoyman
-
Neil Mitchell
-
Nicolas Pouillard
-
Wolfgang Jeltsch