I would like to propose the addition of two new combinators to Control.Monad:
ifM :: (Monad m) => m Bool -> m a -> m a -> m a
whenM :: (Monad m) => m Bool -> m () -> m ()
The reason is that when you work in a `Monad m` the first argument of `if` and `when` is often a `m Bool` and not a `Bool`. In those cases, you have to write:
monadicOperationReturningBool >>= \b -> when b doAnotherMonadicOperation
or
monadicOperationReturningBool >>= flip when doAnotherMonadicOperation
to accomplish what you want to do. If you use the do-notation this is less terrible but you still need to assign a name to the boolean value. Take for example:
f = do
dirDoesntExist <- not <$> doesDirectoryExist path
when dirDoesntExist $ do
putStrLn $ "Creating directory " ++ path
createDirectory path
in this snippet, dirDoesntExist is completely useless and its only purpose it to be used in the next expression. With the new combinators you could write:
f = whenM (not <$> doesDirectoryExists path) $ do
putStrLn $ "Creating directory " ++ path
createDirectory path
Many libraries on hackage already include these functions (I often use Control.Conditional). For a list see http://holumbus.fh-wedel.de/hayoo/hayoo.html?query=whenM&start=0.
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://www.haskell.org/mailman/listinfo/libraries