Control.Monad proposal: Add whenJust

Edward Kmett ekmett at gmail.com
Fri May 10 13:16:53 CEST 2013


I'm -1 on this, due to it just further obfuscating the fact that
Data.Foldable.for_ already exists.


On Fri, May 10, 2013 at 2:13 AM, Niklas Hambüchen <mail at nh2.me> wrote:

> I would like to propose the addition of
>
> whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
> whenJust (Just x) f = f x
> whenJust _        _ = return ()
>
> to Control.Monad, in the section
>
>    "Conditional execution of monadic expressions"
>
> next to
>
>    guard :: MonadPlus m => Bool -> m ()
>    when :: Monad m => Bool -> m () -> m ()
>    unless :: Monad m => Bool -> m () -> m ()
>
>
> Why?
>
> It would allow us to write more readable code and fit well into the
> group of similar functions of this style.
>
> Compare
>
>    mUser <- lookupUser
>
>    whenJust mUser email
>
> or
>
>    whenJust mUser $ \user -> do
>       putStrLn "Mailing!"
>       email user
>
> with some currently available alternatives:
>
>
>    case mUser of
>       Just user -> do putStrLn "Mailing!"
>                       email user
>       Nothing   -> return ()
>
> (Default base case clutter.)
>
>
>    import Data.Foldable
>
>    forM_ mUser $ \user -> do
>      putStrLn "Mailing!"
>      email user
>
> (Not too intuitive/well-named here and "Ambiguous occurrence forM_"
> clash with Control.Monad.)
>
> Some more dissatisfying alternatives:
>
>
>    maybe (return ()) (\user -> do putStrLn "Mailing!"
>                                   email user
>                      ) mUser
>
>
>    flip (maybe (return ())) mUser $ \user -> do
>      putStrLn "Mailing!"
>      email user
>
>
>    import Control.Monad.Trans.Maybe
>    import Control.Monad.Trans (lift)
>
>    _ <- runMaybeT $ return mUser >>= \user -> lift $ do
>      putStrLn "Mailing!"
>      email user
>    return ()
>
>
> Alternative names:
>
>    - withJust, analog to withFile and withForeignPtr
>
> Any comments?
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20130510/ad34bbe5/attachment.htm>


More information about the Libraries mailing list