Control.Monad proposal: Add whenJust

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Fri May 10 16:25:04 CEST 2013


-1

Wasn't there a similar proposal to this last year?

On 10 May 2013 22:04, Simon Hengel <sol at typeful.net> wrote:
> -1
>
> Personally I think forM_ is the way to go.
>
> On Fri, May 10, 2013 at 02:13:45PM +0800, Niklas Hambüchen 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
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries



-- 
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
http://IvanMiljenovic.wordpress.com



More information about the Libraries mailing list