Control.Monad proposal: Add whenJust

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?

-0.5: it looks useful, but it's not that much shorter than flip (maybe (return ())), and there's the cost of library clutter. On 10/05/2013 07:13, 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@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Another alternative is Data.Foldable.for_, which doesn't clash like
Data.Foldable.forM_
On Fri, May 10, 2013 at 2:28 AM, Ganesh Sittampalam
-0.5: it looks useful, but it's not that much shorter than flip (maybe (return ())), and there's the cost of library clutter.
On 10/05/2013 07:13, 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@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

adam vogt
writes:
Another alternative is Data.Foldable.for_, which doesn't clash like Data.Foldable.forM_
-1 on a specific whenJust when we have the more general for_ in Foldable. I use for_ often for the exact usage proposed here. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net

On Fri, 10 May 2013, Niklas Hambüchen wrote:
(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.)
I am against adding a new function to Control.Monad. You should always import with explicit identifier lists or with qualification in order to allow a larger range of imported library versions and then it makes no difference whether you write import Control.Monad (forM_) or import Data.Foldable (forM_)

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
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@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I like it, I have a local whenJust I use very frequently.
I know about forM_, but I don't use it because it sounds too much like a loop.
But I recall we already had this discussion and it failed to catch on
then, so unless something has changed it might not be worth bringing
it up again.
On Fri, May 10, 2013 at 1:13 PM, Niklas Hambüchen
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@haskell.org http://www.haskell.org/mailman/listinfo/libraries

2013/5/10 Evan Laforge
I know about forM_, but I don't use it because it sounds too much like a loop.
I'd say `forM_` is more like "for each" for a collection (rather than C-style "for" loop), which makes perfect sense for Maybe. So I prefer `forM_` instead of adding a new function. Petr

-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@haskell.org http://www.haskell.org/mailman/listinfo/libraries

-1
Wasn't there a similar proposal to this last year?
On 10 May 2013 22:04, Simon Hengel
-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@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

+1 I use whenJust quite frequently and it is much more readable than for_ (wrong connotation) or flip (maybe $ return ()) Cheers, Andreas On 10.05.13 8:13 AM, 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@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

For what it's worth, F# has Option.iter, analogous to List.iter, Array.iter etc: http://msdn.microsoft.com/en-GB/library/ee340387.aspx I did find it a bit funny initially but it's grown on me. Ganesh On 10/05/2013 15:02, Andreas Abel wrote:
+1
I use whenJust quite frequently and it is much more readable than for_ (wrong connotation) or
flip (maybe $ return ())
Cheers, Andreas
On 10.05.13 8:13 AM, 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@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 05/10/2013 09:28 PM, Bardur Arantsson wrote:
On 05/10/2013 08:13 AM, Niklas Hambüchen wrote:
I would like to propose the addition of
-1
(forM_ may not be the best name, but Hoogle will usually find what you want.)
True, I just tested it http://www.haskell.org/hoogle/?hoogle=%28Maybe%20a%29%20-%3E%20%28a%20-%3E%2... and forM_ and for_ are the second and the third result (with colors nicely indicating that "Maybe a" corresponds to "t a").
participants (13)
-
adam vogt
-
Andreas Abel
-
Bardur Arantsson
-
Edward Kmett
-
Evan Laforge
-
Ganesh Sittampalam
-
Henning Thielemann
-
Ivan Lazar Miljenovic
-
John Wiegley
-
kudah
-
Niklas Hambüchen
-
Petr Pudlák
-
Simon Hengel