Adding an ignore function to Control.Monad

wren ng thornton wren at community.haskell.org
Thu Jun 11 19:42:28 EDT 2009


John Meacham wrote:
> And here I always get annoyed by types that specify '()' explicitly when
> a universally quantified type will do. (`when` and `unless` are
> particularly offensive in this regard). Forcing idioms to be more
> verbose than necessary obscures intent. 

Indeed. In my personal libraries for scripting Haskell I define:

     infixr 8 `returning`
     {-# INLINE returning #-}
     returning      :: (Monad m) => (a -> m b) -> (a -> m a)
     f `returning` x = f x >> return x

precisely to get around this annoyance. The one I find particularly 
offensive is MonadState.put.

In general, I find the use of () for what C-like languages would call 
void is a sign of excessive imperativism. If C had any measure of 
compositionality then it wouldn't be returning void either. Indeed, you 
can often see this corrected in the style of OOP where putatively void 
method returns the current object instead, so that they support method 
chaining, aka applicative style. There are certainly functions which 
should return () ---e.g. with the OOP analogy again, methods to close a 
file handle, destroy an object, etc--- but functions which should accept 
only () seem quite rare.


> Do we have any data that accidentally ignoring return values is a
> problem in practice?

There is the memory leak (or stack overflow) problems of using mapM or 
sequence when the result is unused. I'm not sure if these fall under 
your "confused someone once" category, but they can be pernicious. This 
is potentially solvable by the compiler rewriting to mapM_ and sequence_ 
when it detects the result is unused; though whether that's the best 
solution is unclear.

-- 
Live well,
~wren


More information about the Libraries mailing list