Counter proposal: Do not include whenM and ifM

Tom Ellis tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Mon Apr 21 16:55:58 UTC 2014


(Since Carter asked for new proposals to be started in a separate thread I
am reposting the contents of an earlier message with additions)

My (counter) proposal is that 'whenM' and 'ifM' *not* be added anywhere
(under any names) because there is a completely generic alternative to these
adhoc additions that warrants further investigation.

The executive summary is that instead of introducing another function
'unlessM' to be used like this

    unlessM doesDirectoryExist path $ do
        putStrLn $ "Creating directory " ++ path
        createDirectory path

we just use the existing 'unless' and a new generic combinator (<*>|) like
this

    unless <$> doesDirectoryExist path <*>| pure (do
        putStrLn $ "Creating directory " ++ path
        createDirectory path)

I have been reading the discussion about 'whenM' and 'ifM' wondering where
it is going to end.  Presumably we will also have 'unlessM'.  Then 'guardM'
becomes a reasonable candidate, and indeed 'libraryFunctionM' for any
'libraryFunction' that happens to have a monadic return type and non-monadic
argument.  It is as if everyone is discussing how many 'liftAn' we should
provide when (<$>) and (<*>) already do the job generically.

The generic alternative that I believe warrants further investigation is to
add an operator called, for example, (<*>|) to be read as "apply and done". 
All these specific questions about whether a function should take a monadic
argument or not are solved generically by (<$>), (<*>) and (<*>|) as
demonstrated below.

It is no more complex than just using the Applicative combinators (<$>) and
(<*>) we know and love.

It seems the discussion about 'mif' vs 'ifM' can be completely finessed. 
Those functions are no more convenient than (<*>|) syntax.  There may be an
even better syntax than the one I propose here but I think it's actually
pretty good as it is.

I would appreciate some feedback on this.

Tom




import Control.Monad
import Control.Applicative
-- vv For the example!
import System.Directory

-- The operator, read as "apply and done", for applying a monadic
-- argument and completing the chain of applications.

infixl 4 <*>|

(<*>|) :: Monad m => m (a -> m b) -> m a -> m b
f <*>| x = join (f `ap` x)

-- Suppose we have an 'f' that takes some monadic arguments and some pure
-- arguments

f :: Monad m => Int -> Bool -> m Char -> Float -> m Double -> m Integer
f = undefined

-- Then we just use Applicative combinators plus (<*>|) to apply monadic
-- arguments

fM :: (Monad m, Applicative m) =>
      m Int -> m Bool -> m Char -> m Float -> m Double -> m Integer
fM a b c d e = f <$> a <*> b <*> pure c <*> d <*>| pure e

-- Here's another example

f' :: Monad m =>
      Int -> Bool -> m Char -> Float -> m Double -> String -> m Integer
f' = undefined

-- Not all of the arguments to the result need to be monadic.  We can keep
-- some pure if we like.

f'M :: (Monad m, Applicative m) =>
       m Int -> Bool -> m Char -> Float -> m Double -> m String -> m Integer
f'M a b c d e f = f' <$> a <*> pure b <*> pure c <*> pure d <*> pure e <*>| f

-- Implementing whenM, unlessM and ifM is easy.

whenM :: (Monad m, Applicative m) => m Bool -> m () -> m ()
whenM cond action = when <$> cond <*>| pure action

unlessM :: (Monad m, Applicative m) => m Bool -> m () -> m ()
unlessM cond action = unless <$> cond <*>| pure action

if_ :: Bool -> a -> a -> a
if_ cond then_ else_ = if cond then then_ else else_

ifM :: (Monad m, Applicative m) => m Bool -> m () -> m () -> m ()
ifM cond then_ else_ = if_ <$> cond <*> pure then_ <*>| pure else_

-- But the point is that you don't actually need whenM, unlessM or ifM,
-- since it's easy to feed arguments to when, unless and if_ directly.

path = undefined

usingUnless = unless <$> doesDirectoryExist path <*>| pure (do
  putStrLn $ "Creating directory " ++ path
  createDirectory path)


More information about the Libraries mailing list