
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