Adding an ignore function to Control.Monad

Maurí­cio briqueabraque at yahoo.com
Wed Jun 10 13:44:36 EDT 2009


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 <michael at snoyman.com 
> <mailto:michael at 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.html.
>     He also uses the name "ignore" for your function.
> 
>     Michael
> 
> 
>     On Wed, Jun 10, 2009 at 7:53 PM, Gwern Branwen <gwern0 at gmail.com
>     <mailto:gwern0 at 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 at haskell.org <mailto:Libraries at haskell.org>
>         http://www.haskell.org/mailman/listinfo/libraries
> 
> 
> 
>     _______________________________________________
>     Libraries mailing list
>     Libraries at haskell.org <mailto:Libraries at haskell.org>
>     http://www.haskell.org/mailman/listinfo/libraries
> 
> 
> 
> ------------------------------------------------------------------------
> 
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries



More information about the Libraries mailing list