Proposal: add ifM and whenM to Control.Monad

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.

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 +1 for both, plus unlessM :: (Monad m) => m Bool -> m () -> m () unlessM mc ma = ifM mc (return ()) ma (See, for instance, https://hackage.haskell.org/package/Agda-2.3.2.2/docs/Agda-Utils-Monad.html .) On 20.04.2014 21:10, Mario Pastorelli wrote:
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
- -- Andreas Abel <>< Du bist der geliebte Mensch. Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden andreas.abel@gu.se http://www2.tcs.ifi.lmu.de/~abel/ -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.11 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iEYEARECAAYFAlNUIiQACgkQPMHaDxpUpLMkiQCgwwUfJ/orQ9GNB3SsStc1SB/4 F/kAn0AZ04HBeRjlNk7QkZcjHZ6Am+37 =EBzJ -----END PGP SIGNATURE-----

+1 for unlessM On 04/20/2014 09:38 PM, Andreas Abel wrote:
-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
+1 for both, plus
unlessM :: (Monad m) => m Bool -> m () -> m () unlessM mc ma = ifM mc (return ()) ma
(See, for instance, https://hackage.haskell.org/package/Agda-2.3.2.2/docs/Agda-Utils-Monad.html .)
On 20.04.2014 21:10, Mario Pastorelli wrote:
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
- -- Andreas Abel <>< Du bist der geliebte Mensch.
Department of Computer Science and Engineering Chalmers and Gothenburg University, Sweden
andreas.abel@gu.se http://www2.tcs.ifi.lmu.de/~abel/ -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.11 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/
iEYEARECAAYFAlNUIiQACgkQPMHaDxpUpLMkiQCgwwUfJ/orQ9GNB3SsStc1SB/4 F/kAn0AZ04HBeRjlNk7QkZcjHZ6Am+37 =EBzJ -----END PGP SIGNATURE-----

+1 for finally adding ifM, whenM, and unlessM to Control.Monad (what about guardM?) As far as bike-shedding goes, the naming-convention abiding mif, mwhen, and munless are also fine— albeit they look a bit strange. While the official fooM vs mfoo convention is spelled out in Control.Monad, I don't know how much anyone actually pays attention to that; a lot of people use the fooM pattern ubiquitously instead. In practice the mfoo pattern is only used with mzero, mplus, msum, and mfilter— so in practice it seems more like "mfoo means the MonadPlus variant of foo" whereas "fooM means the Monad variant of foo". -- Live well, ~wren

I don't understand how the existing naming convention for promoting
functions to monadic versions can apply to when/unless since they already
operate on monads.
I would hesitate to use an 'm' prefix for monadic code is because the
Monoid typeclass does that (mempty, mappend, mconcat).
I would support a change in the documented convention for the 'm' prefix to
only being used for MonadPlus (in addition to Monoid).
+1 on whenM and unlessM
I haven't found myself needing ifM, but I will look at my code and see if I
was missing opportunities to make it nicer.
On Sun, Apr 20, 2014 at 4:22 PM, wren romano
+1 for finally adding ifM, whenM, and unlessM to Control.Monad (what about guardM?)
As far as bike-shedding goes, the naming-convention abiding mif, mwhen, and munless are also fine— albeit they look a bit strange. While the official fooM vs mfoo convention is spelled out in Control.Monad, I don't know how much anyone actually pays attention to that; a lot of people use the fooM pattern ubiquitously instead. In practice the mfoo pattern is only used with mzero, mplus, msum, and mfilter— so in practice it seems more like "mfoo means the MonadPlus variant of foo" whereas "fooM means the Monad variant of foo".
-- Live well, ~wren _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

These come up every few months. Historically, I've always been -1 on their inclusion as they are simple compositions of more fundamental operations. However, given that they keep getting reinvented with the exact same names and functionality. I'm finally ready to give in. +1 from me. -Edward On Sun, Apr 20, 2014 at 3:10 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
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

Edward Kmett
writes:
However, given that they keep getting reinvented with the exact same names and functionality. I'm finally ready to give in.
+1 from me.
How about a more general combinator, like om (name needed)? om :: Monad m => (a -> b -> m c) -> m a -> b -> m c om f m = (m >>=) . flip f whenM = om when unlessM = om unless etc. John

I still don't like 'om', naming aside.
ifM, whenM and unlessM are at least something folks expect to find, so
supplying names for those things that people actually go looking for is one
thing. They are repeatedly reinvented using exactly those names, so I can
see just adding them where people expect to find them, if only so we can
stop repeating this conversation every 6 months.
They are also at least a bit of a composition, so they aren't just a
trivial restriction of another combinator with broader range of
applicability, that we'd like users to learn how to use in its full
generality.
On the other hand supplying something like 'om' is awkward to motivate is
isolation.
It happens to munge a monad on one arg but not the other in a weird special
case just because it happens to unify here. But that doesn't give any real
insight to the user and forces them into a mode where they just have to
memorize that this modifier only works in these couple of cases. 'om'
doesn't really abstract over anything fundamental.
One can't explain why anyone would care about it without reference to the
quirks of two other function signatures.
-Edward
On Sun, Apr 20, 2014 at 5:10 PM, John Wiegley
Edward Kmett
writes: However, given that they keep getting reinvented with the exact same names and functionality. I'm finally ready to give in.
+1 from me.
How about a more general combinator, like om (name needed)?
om :: Monad m => (a -> b -> m c) -> m a -> b -> m c om f m = (m >>=) . flip f
whenM = om when unlessM = om unless
etc.
John _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Apr 20, 2014 at 04:10:34PM -0500, John Wiegley wrote:
Edward Kmett
writes: However, given that they keep getting reinvented with the exact same names and functionality. I'm finally ready to give in. +1 from me.
How about a more general combinator, like om (name needed)?
om :: Monad m => (a -> b -> m c) -> m a -> b -> m c om f m = (m >>=) . flip f
whenM = om when unlessM = om unless
How about a completely general way of feeding arguments into a function, some of which are in a monad, some not? All you need is a combinator (<*>|) which indicates when you've supplied all the arguments. It can be read as "done" or something like that. Using it looks a bit odd but could be neatened up at the expense of adding even *more* combinators! Anyway, it completely obviates the need for ifM/whenM/unlessM and om, as far as I can tell. Tom import Control.Monad import System.Directory import Control.Applicative import Control.Lens infixl 4 <*>| (<*>|) :: Monad m => m (a -> m b) -> m a -> m b f <*>| x = join (f `ap` x) -- Here's how you can mix arguments in a monad with those that are not f :: Monad m => a -> b -> m c -> d -> m e -> m f f = undefined g :: (Monad m, Applicative m) => m a -> m b -> m c -> m d -> m e -> m f g a b c d e = f <$> a <*> b <*> pure c <*> pure d <*>| pure e -- Here's another example f' :: Monad m => a -> b -> m c -> d -> m e -> f -> m g f' = undefined g' :: (Monad m, Applicative m) => m a -> m b -> m c -> m d -> m e -> m f -> m g g' a b c d e f = f' <$> a <*> b <*> pure c <*> pure d <*> pure e <*>| f -- Implementing whenM and unlessM is easy. No om required. whenM :: (Monad m, Applicative m) => m Bool -> m () -> m () whenM cond action = when <$> cond <*>| pure action unlessM :: (Monad m, Applicative m) => m Bool -> m () -> m () unlessM cond action = unless <$> cond <*>| pure action -- But the point is that you don't actually need whenM and unlessM, since -- it's easy to feed arguments to when and unless directly. path = undefined usingUnless = unless <$> doesDirectoryExist path <*>| pure (do putStrLn $ "Creating directory " ++ path createDirectory path)

Hi Mario, On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool): f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr

Hi Herbert, in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of f = unlessM (doesDirectoryExist path) $ do putStrLn $ "Creating directory " ++ path createDirectory path In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate. While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions. On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 () [...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path
Cheers, hvr

The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/ The functions in this library use the following naming conventions:
- A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
- A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
- A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names. I don't think the convention has been documented in Control.Monad itself for years. -Edward On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do
dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

My mistake. These rules are still in Control.Monad. I just scrolled right
past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
- A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
- A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
- A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do
dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I see. Another solution is to use if', when' and unless'. On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
mailto:ekmett@gmail.com> wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
* A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
* A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
* A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs. On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
- A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
- A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
- A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do
dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

when' and unless' are good names in my opinion. In Haskell libs ' is often used to define a similar function to another one. For if' we could use the third convention. Its type is: if :: Bool -> a -> a -> a and by prefixing 'm' we can change it to be monadic: mif :: (Monad m) => m Bool -> m a -> m a -> m a that stands for monadic if. I don't like the idea of having different name notations for ifM and whenM/unlessM but that's true also for if-then-else and when/unless. I personally don't like the name 'mif' but I don't see many other solutions. Maybe the name 'if' isn't appropriate and it's better to change it into something else? On 04/20/2014 11:48 PM, Edward Kmett wrote:
if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
mailto:ekmett@gmail.com> wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
* A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
* A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
* A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

i'm slightly meh about that Idea because i'll keep on misreading it as "milf" rather than "mif" On Sun, Apr 20, 2014 at 6:22 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
when' and unless' are good names in my opinion. In Haskell libs ' is often used to define a similar function to another one.
For if' we could use the third convention. Its type is:
if :: Bool -> a -> a -> a
and by prefixing 'm' we can change it to be monadic:
mif :: (Monad m) => m Bool -> m a -> m a -> m a
that stands for monadic if. I don't like the idea of having different name notations for ifM and whenM/unlessM but that's true also for if-then-else and when/unless. I personally don't like the name 'mif' but I don't see many other solutions. Maybe the name 'if' isn't appropriate and it's better to change it into something else?
On 04/20/2014 11:48 PM, Edward Kmett wrote:
if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
- A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
- A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
- A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do
dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ 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

mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure. The principal use of ' in base is for adding strictness, and when' and unless' don't fit that pattern. Looking at it in code doesn't send a signal that most users would pick up that an extra monadic effect is going on. -Edward On Sun, Apr 20, 2014 at 6:22 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
when' and unless' are good names in my opinion. In Haskell libs ' is often used to define a similar function to another one.
For if' we could use the third convention. Its type is:
if :: Bool -> a -> a -> a
and by prefixing 'm' we can change it to be monadic:
mif :: (Monad m) => m Bool -> m a -> m a -> m a
that stands for monadic if. I don't like the idea of having different name notations for ifM and whenM/unlessM but that's true also for if-then-else and when/unless. I personally don't like the name 'mif' but I don't see many other solutions. Maybe the name 'if' isn't appropriate and it's better to change it into something else?
On 04/20/2014 11:48 PM, Edward Kmett wrote:
if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
- A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
- A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
- A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do
dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 04/21/2014 12:35 AM, Edward Kmett wrote:
mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure.
Good!
The principal use of ' in base is for adding strictness, and when' and unless' don't fit that pattern. Looking at it in code doesn't send a signal that most users would pick up that an extra monadic effect is going on.
You are right about the fact that they don't recall the fact that they are monadic versions. The problem is that without prepending or appending the letter 'm', how can we make clear to the user that it is the monadic version of another function? The only solution is to find other names but that's also bad in my opinion. What about adding a new rule? Appending 'm' lowercase instead of 'M' uppercase stands for an alternative version of a function with the first argument monadic. So forM follows the first rule while whenm follows the new rule. Bonus: also if could be defined as ifm :: (Monad m) => m Bool -> a -> a -> a.
-Edward
On Sun, Apr 20, 2014 at 6:22 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: when' and unless' are good names in my opinion. In Haskell libs ' is often used to define a similar function to another one.
For if' we could use the third convention. Its type is:
if :: Bool -> a -> a -> a
and by prefixing 'm' we can change it to be monadic:
mif :: (Monad m) => m Bool -> m a -> m a -> m a
that stands for monadic if. I don't like the idea of having different name notations for ifM and whenM/unlessM but that's true also for if-then-else and when/unless. I personally don't like the name 'mif' but I don't see many other solutions. Maybe the name 'if' isn't appropriate and it's better to change it into something else?
On 04/20/2014 11:48 PM, Edward Kmett wrote:
if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
mailto:ekmett@gmail.com> wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
* A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
* A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
* A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 2014-04-21 at 00:35:03 +0200, Edward Kmett wrote:
mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure.
I'm +1 on using `mif`/`mwhen`/`munless` (assuming all those pass the current naming convention), because otherwise adding an exception to the naming convention for Control.Monad entities would also require rewording the existing naming convention in the Haskell Report. Moreover, since 'Control.Monad' is often imported unqualified, we'd probably cause clashes in existing packages (and together with non-PVP upper-bounds on base that'd mean build failures) A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM: ,---- | $ zgrep -l '^\(when\|if\|unless\)M ' -- *.tar.gz | Adaptive-0.23.tar.gz | Adaptive-Blaisorblade-0.23.tar.gz | Agda-2.3.2.2.tar.gz | alms-0.6.5.tar.gz | alpha-1.0.15.tar.gz | apelsin-1.2.3.tar.gz | aws-sdk-0.12.4.tar.gz | bamboo-2010.2.25.tar.gz | bff-mono-0.2.1.tar.gz | bool-extras-0.4.0.tar.gz | btree-concurrent-0.1.5.tar.gz | buildbox-2.1.4.1.tar.gz | caldims-0.1.0.tar.gz | cao-0.1.1.tar.gz | clafer-0.3.5.1.tar.gz | Coadjute-0.1.1.tar.gz | Commando-1.0.0.4.tar.gz | concurrent-extra-0.7.0.6.tar.gz | cond-0.4.0.2.tar.gz | control-bool-0.2.1.tar.gz | control-monad-loop-0.1.tar.gz | ctrie-0.1.0.1.tar.gz | custom-prelude-0.2.2.0.tar.gz | darcs-benchmark-0.1.9.tar.gz | data-spacepart-20090215.0.tar.gz | DPM-0.3.0.0.tar.gz | feldspar-language-0.6.0.3.tar.gz | fix-imports-1.0.3.tar.gz | fquery-0.2.1.5.tar.gz | git-annex-5.20140412.tar.gz | github-backup-1.20131203.tar.gz | git-repair-1.20140227.tar.gz | hjs-0.2.1.tar.gz | hsc3-graphs-0.14.1.tar.gz | hsConfigure-0.1.tar.gz | hxt-filter-8.4.2.tar.gz | IfElse-0.85.tar.gz | infinity-0.3.tar.gz | JYU-Utils-0.1.1.2.tar.gz | kure-2.14.6.tar.gz | language-sh-0.0.3.1.tar.gz | lhae-0.0.3.tar.gz | libcspm-1.0.0.tar.gz | liquid-fixpoint-0.1.0.0.tar.gz | LslPlus-0.4.3.tar.gz | manatee-core-0.1.1.tar.gz | MiniAgda-0.2014.1.9.tar.gz | omega-1.5.2.tar.gz | orchid-0.0.8.tar.gz | panda-2009.4.1.tar.gz | processing-1.2.0.1.tar.gz | propellor-0.5.0.tar.gz | regexpr-0.5.4.tar.gz | rosso-1.0.tar.gz | runghc-0.1.0.2.tar.gz | scion-0.1.0.2.tar.gz | scyther-proof-0.8.0.0.tar.gz | shellish-0.1.4.tar.gz | shelly-1.5.2.tar.gz | sindre-0.4.tar.gz | spacepart-0.1.0.0.tar.gz | Strafunski-StrategyLib-5.0.0.3.tar.gz | StrategyLib-4.0.0.0.tar.gz | tamarin-prover-utils-0.8.5.1.tar.gz | test-sandbox-0.0.1.7.tar.gz | usb-1.2.tar.gz | vhd-0.2.2.tar.gz | watcher-0.0.3.0.tar.gz | wxc-0.90.1.1.tar.gz | YampaSynth-0.1.2.tar.gz | yesod-bin-1.2.8.1.tar.gz | yi-0.8.1.tar.gz | yjtools-0.9.18.tar.gz | zip-conduit-0.2.2.1.tar.gz | zoom-0.1.0.1.tar.gz `---- ...whereas a grep on the `m`-prefixed versions turns up much less hits: ,---- | $ zgrep -l '^m\(when\|if\|unless\) ' -- *.tar.gz | bool-extras-0.4.0.tar.gz | ideas-1.1.tar.gz `---- Cheers, hvr

A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question: Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention? If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here. In general, I'm not sure about ifM (as it does not line up with `bool`). Cheers, Simon

On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM: But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they are like me, they probably were ignoring the naming convention and used the most intuitive name. Once you know forM then it's obvious that you append 'M' to functions that "are more monadic". Probably mif, mwhen and munless are more compatible with the API rules.
In general, I'm not sure about ifM (as it does not line up with `bool`).
This is the second time that I read about `bool` but I can't find it. Can somebody provide a link to it? mbool can be a solution, but not as intuitive as mif. Mario

On Mon, Apr 21, 2014 at 11:35:49AM +0200, Mario Pastorelli wrote:
This is the second time that I read about `bool` but I can't find it. Can somebody provide a link to it? mbool can be a solution, but not as intuitive as mif.
It's new. https://www.fpcomplete.com/hoogle?q=bool&env=ghc-7.8-unstable http://haddocks.fpcomplete.com/fp/7.7/20131212-1/base/Data-Bool.html#v:bool

I still believe in the intelligence of the masses, in particular when it comes to the evolution of vocabulary. Hayoo gives me 14 hits on "ifM", and 0 on "mif". +1 to ifM/whenM/unlessM -1 to mif/mwhen/munless CustomPrelude. ifM :: m Bool -> m a -> m a -> m a custom-prelude Control.Conditional. ifM :: m bool -> m a -> m a -> m a cond Bamboo.Helper. ifM :: m Bool -> m b -> m b -> m b bamboo Control.Monad.Tools. ifM :: m Bool -> m a -> m a -> m a yjtools Agda.Utils.Monad. ifM :: m Bool -> m a -> m a -> m a Agda Sindre.Util. ifM :: m Bool -> m a -> m a -> m a sindre Language.KURE.Combinators.Monad. ifM :: m Bool -> m a -> m a -> m a kure Test.WebDriver.Commands.Wait. ifM :: m bool -> m a -> m a -> m a webdriver Language.Fixpoint.Misc. ifM :: m Bool -> m a -> m a -> m a liquid-fixpoint Scion.Utils. ifM :: m Bool -> m a -> m a -> m a scion Feldspar.Core.Frontend.ConditionM. ifM :: Data Bool -> M a -> M a -> M a feldspar-language Control.Monad.Rosso1. ifM :: m Bool -> m a -> m a -> m a rosso Control.Monad.Adaptive.MonadUtil. ifM :: m Bool -> m a -> m a -> m a Adaptive-Blaisorblade Control.Monad.Adaptive.MonadUtil. ifM :: m Bool -> m a -> m a -> m a Adaptive On 21.04.14 11:35 AM, Mario Pastorelli wrote:
On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM: But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they are like me, they probably were ignoring the naming convention and used the most intuitive name. Once you know forM then it's obvious that you append 'M' to functions that "are more monadic". Probably mif, mwhen and munless are more compatible with the API rules.
In general, I'm not sure about ifM (as it does not line up with `bool`).
This is the second time that I read about `bool` but I can't find it. Can somebody provide a link to it? mbool can be a solution, but not as intuitive as mif.
Mario _______________________________________________ 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 same reason as Andreas:
+1 to ifM/whenM/unlessM
On 21 April 2014 11:30, Andreas Abel
I still believe in the intelligence of the masses, in particular when it comes to the evolution of vocabulary.
Hayoo gives me 14 hits on "ifM", and 0 on "mif".
+1 to ifM/whenM/unlessM -1 to mif/mwhen/munless
CustomPrelude. ifM :: m Bool -> m a -> m a -> m a custom-prelude
Control.Conditional. ifM :: m bool -> m a -> m a -> m a cond
Bamboo.Helper. ifM :: m Bool -> m b -> m b -> m b bamboo
Control.Monad.Tools. ifM :: m Bool -> m a -> m a -> m a yjtools
Agda.Utils.Monad. ifM :: m Bool -> m a -> m a -> m a Agda
Sindre.Util. ifM :: m Bool -> m a -> m a -> m a sindre
Language.KURE.Combinators.Monad. ifM :: m Bool -> m a -> m a -> m a kure
Test.WebDriver.Commands.Wait. ifM :: m bool -> m a -> m a -> m a webdriver
Language.Fixpoint.Misc. ifM :: m Bool -> m a -> m a -> m a liquid-fixpoint
Scion.Utils. ifM :: m Bool -> m a -> m a -> m a scion
Feldspar.Core.Frontend.ConditionM. ifM :: Data Bool -> M a -> M a -> M a feldspar-language
Control.Monad.Rosso1. ifM :: m Bool -> m a -> m a -> m a rosso
Control.Monad.Adaptive.MonadUtil. ifM :: m Bool -> m a -> m a -> m a Adaptive-Blaisorblade
Control.Monad.Adaptive.MonadUtil. ifM :: m Bool -> m a -> m a -> m a Adaptive
On 21.04.14 11:35 AM, Mario Pastorelli wrote:
On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit
of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they are like me, they probably were ignoring the naming convention and used the most intuitive name. Once you know forM then it's obvious that you append 'M' to functions that "are more monadic". Probably mif, mwhen and munless are more compatible with the API rules.
In general, I'm not sure about ifM (as it does not line up with `bool`).
This is the second time that I read about `bool` but I can't find it. Can somebody provide a link to it? mbool can be a solution, but not as intuitive as mif.
Mario _______________________________________________ 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/
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- *Alois Cochard* http://aloiscochard.blogspot.com http://twitter.com/aloiscochard http://github.com/aloiscochard

http://hackage.haskell.org/package/base-4.7.0.0/docs/src/Data-Bool.html#bool On Mon, Apr 21, 2014 at 5:35 AM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit
of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they are like me, they probably were ignoring the naming convention and used the most intuitive name. Once you know forM then it's obvious that you append 'M' to functions that "are more monadic". Probably mif, mwhen and munless are more compatible with the API rules.
In general, I'm not sure about ifM (as it does not line up with `bool`).
This is the second time that I read about `bool` but I can't find it. Can somebody provide a link to it? mbool can be a solution, but not as intuitive as mif.
Mario

Thank you. So bool takes the predicate as last argument, good for combining it with a monadic operation: doesDirectoryExists path >>= bool (putStrLn ("Creating dir " ++ path) >> createDirectory path) (putStrLn ("Directory already exists")) I still prefer the version using mif/ifM, in particular when working with IO: ifM (doesDirectoryExists path) (putStrLn ("Directory already exists")) (putStrLn ("Creating dir " ++ path) >> createDirectory path) On 04/21/2014 02:16 PM, Edward Kmett wrote:
http://hackage.haskell.org/package/base-4.7.0.0/docs/src/Data-Bool.html#bool
On Mon, Apr 21, 2014 at 5:35 AM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they are like me, they probably were ignoring the naming convention and used the most intuitive name. Once you know forM then it's obvious that you append 'M' to functions that "are more monadic". Probably mif, mwhen and munless are more compatible with the API rules.
In general, I'm not sure about ifM (as it does not line up with `bool`).
This is the second time that I read about `bool` but I can't find it. Can somebody provide a link to it? mbool can be a solution, but not as intuitive as mif.
Mario

On Mon, Apr 21, 2014 at 5:35 AM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit
of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they
The API is there to serve its users, not really to dictate to them. If the common convention is counter to the API structure, perhaps it is the API that should change. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 On 21/04/14 14:55, Brandon Allbery wrote:
The API is there to serve its users, not really to dictate to them. If the common convention is counter to the API structure, perhaps it is the API that should change. This is myopic. Please consider how many people use Haskell and the ramifications if you just change the naming conventions, thereby renaming tens of functions.
Alexander alexander@plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlNVFcgACgkQRtClrXBQc7VPBAD9GZSiYdVivUKKkWqCv6YQWQED IMnxABKs6JdHXaA9Bj8BAJo2dHATp00UhOIcw6PPqfCX4ddGj+zspec04dyq84ob =CoKy -----END PGP SIGNATURE-----

On Mon, Apr 21, 2014 at 8:55 AM, Brandon Allbery
On Mon, Apr 21, 2014 at 5:35 AM, Mario Pastorelli
wrote: On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they
The API is there to serve its users, not really to dictate to them. If the common convention is counter to the API structure, perhaps it is the API that should change.
Has anyone noticed yet that replicateM is already breaking the ostensibly established naming scheme, and should properly be named mreplicate? Also, sequenceA is clearly echoing the fooM convention but it breaks the pattern even worse. But perhaps we should in fact rename replicateM. Certainly "mreplicate" would fit in better with other monadic variants of list functions, like "mconcat"! Consistency is important, after all. Also, mfix should probably be fixM, for what that's worth. - C.

On 04/21/2014 04:22 PM, Casey McCann wrote:
On Mon, Apr 21, 2014 at 8:55 AM, Brandon Allbery
wrote: On Mon, Apr 21, 2014 at 5:35 AM, Mario Pastorelli
wrote: On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM: But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they
The API is there to serve its users, not really to dictate to them. If the common convention is counter to the API structure, perhaps it is the API that should change. Has anyone noticed yet that replicateM is already breaking the ostensibly established naming scheme, and should properly be named mreplicate?
Sadly, replicateM breaks the naming scheme in a different way than ifM. The first doesn't justify the existence of the latter. replicate :: Int -> a -> [a] replicateM :: Monad m => Int -> m a -> m [a] if :: Bool -> a -> a -> a ifM :: Monad m => m Bool -> m a -> m a -> m a Only the name 'mif' respects the rules with this type. The more generic version of 'ifM' is ifM :: Monad m => m Bool -> a -> a -> a and I don't think there is a name conversion for this kind of function in Control.Monad.
But perhaps we should in fact rename replicateM. Certainly "mreplicate" would fit in better with other monadic variants of list functions, like "mconcat"! Consistency is important, after all.
Also, mfix should probably be fixM, for what that's worth.
Don't you think that for compatibility reason this can be very problematic? How many people already used replicateM (and replicateM_) in their code? How many times?

On Mon, Apr 21, 2014 at 11:33 AM, Mario Pastorelli
On 04/21/2014 04:22 PM, Casey McCann wrote:
Has anyone noticed yet that replicateM is already breaking the ostensibly established naming scheme, and should properly be named mreplicate?
Sadly, replicateM breaks the naming scheme in a different way than ifM. The first doesn't justify the existence of the latter.
But it does somewhat deflate the notion that the fooM convention is consistently used, especially since replicateM and replicateM_ are probably more frequently used than many of the properly-named functions.
But perhaps we should in fact rename replicateM. Certainly "mreplicate" would fit in better with other monadic variants of list functions, like "mconcat"! Consistency is important, after all.
Also, mfix should probably be fixM, for what that's worth.
Don't you think that for compatibility reason this can be very problematic? How many people already used replicateM (and replicateM_) in their code? How many times?
Ah, so you're arguing that API consistency is sometimes outweighed by other concerns? I suppose I can't disagree with that. ;] Naming things is a matter of human language, and as a rule of thumb if everyone consistently breaks a linguistic "rule" in exactly the same way, it was the wrong rule. Figuring out what the actual rule being followed is and making it explicit is far more useful than trying to force a rule that runs counter to intuition. These functions have been reinvented many, many times under the names ifM &c., and between that and the strong association between the m prefix and MonadPlus/Monoid (as demonstrated by the fact you apparently didn't notice I compared "mreplicate" to "mconcat" above) I would argue that mif &c. are actually more misleading in this case, for the clear and simple reason that they're not the names most people would expect. Unless we plan to be absolutely and completely consistent, including renaming replicateM and mfix, we should use the widely established names in this case. - C.

On 04/21/2014 06:03 PM, Casey McCann wrote:
On 04/21/2014 04:22 PM, Casey McCann wrote:
Has anyone noticed yet that replicateM is already breaking the ostensibly established naming scheme, and should properly be named mreplicate?
Sadly, replicateM breaks the naming scheme in a different way than ifM. The first doesn't justify the existence of the latter. But it does somewhat deflate the notion that the fooM convention is consistently used, especially since replicateM and replicateM_ are
On Mon, Apr 21, 2014 at 11:33 AM, Mario Pastorelli
wrote: probably more frequently used than many of the properly-named functions. But perhaps we should in fact rename replicateM. Certainly "mreplicate" would fit in better with other monadic variants of list functions, like "mconcat"! Consistency is important, after all.
Also, mfix should probably be fixM, for what that's worth.
Don't you think that for compatibility reason this can be very problematic? How many people already used replicateM (and replicateM_) in their code? How many times? Ah, so you're arguing that API consistency is sometimes outweighed by other concerns? I suppose I can't disagree with that. ;]
Naming things is a matter of human language, and as a rule of thumb if everyone consistently breaks a linguistic "rule" in exactly the same way, it was the wrong rule. Figuring out what the actual rule being followed is and making it explicit is far more useful than trying to force a rule that runs counter to intuition.
These functions have been reinvented many, many times under the names ifM &c., and between that and the strong association between the m prefix and MonadPlus/Monoid (as demonstrated by the fact you apparently didn't notice I compared "mreplicate" to "mconcat" above) I would argue that mif &c. are actually more misleading in this case, for the clear and simple reason that they're not the names most people would expect.
Unless we plan to be absolutely and completely consistent, including renaming replicateM and mfix, we should use the widely established names in this case.
- C.
Yes, I think you are right. +1 for ifM, whenM and unlessM.

Mario Pastorelli
Only the name 'mif' respects the rules with this type. The more generic version of 'ifM' is
ifM :: Monad m => m Bool -> a -> a -> a
and I don't think there is a name conversion for this kind of function in Control.Monad.
Well, if you could actually implement the above function, convention would likely dictate that it be called "unsafeIf". David

On 04/21/2014 06:56 PM, David Mazieres wrote:
Mario Pastorelli
writes: Only the name 'mif' respects the rules with this type. The more generic version of 'ifM' is
ifM :: Monad m => m Bool -> a -> a -> a
and I don't think there is a name conversion for this kind of function in Control.Monad. Well, if you could actually implement the above function, convention would likely dictate that it be called "unsafeIf".
David
Yes, you are right. That's wrong, please ignore it. The type of ifM is ifM :: Monad m => m Bool -> m a -> m a -> m a so prepending 'm' is ok.

I can write precisely 2 implementations of that function. They probably don't have the semantics you want, however. ;) -Edward On Mon, Apr 21, 2014 at 12:56 PM, David Mazieres < dm-list-haskell-libraries@scs.stanford.edu> wrote:
Mario Pastorelli
writes: Only the name 'mif' respects the rules with this type. The more generic version of 'ifM' is
ifM :: Monad m => m Bool -> a -> a -> a
and I don't think there is a name conversion for this kind of function in Control.Monad.
Well, if you could actually implement the above function, convention would likely dictate that it be called "unsafeIf".
David _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On 04/21/2014 02:55 PM, Brandon Allbery wrote:
On Mon, Apr 21, 2014 at 5:35 AM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they
The API is there to serve its users, not really to dictate to them. If the common convention is counter to the API structure, perhaps it is the API that should change.
I agree with you but I'm not the developer of this API. Considering how important is Control.Monad for Haskell I think it's important to pick the right name for new functions.

I, for one, could get behind just taking ifM, whenM, unlessM for these operations, proper naming conventions aside. They've been independently reinvented in 60+ packages with these exact names. If we do this, over time we'll save another 60+ packages the trouble of doing the same thing. -Edward On Mon, Apr 21, 2014 at 11:38 AM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
On 04/21/2014 02:55 PM, Brandon Allbery wrote:
On Mon, Apr 21, 2014 at 5:35 AM, Mario Pastorelli < pastorelli.mario@gmail.com> wrote:
On 04/21/2014 10:41 AM, Simon Hengel wrote:
A quick heuristic grep over all Hackage packages results in quite a bit
of packages containing the ifM/whenM/unlessM:
But that kind of shows that the "expected" names for those functions are ifM/whenM/unlessM. I would ask the question:
Are there any other useful combinators that would be named ifM/whenM/unlessM under the current naming convention?
If no, then I'm not entirely convinced that we should decide against what seems to be common intuition here.
Breaking API consistency because a lot of people are already doing it doesn't feel right. If they
The API is there to serve its users, not really to dictate to them. If the common convention is counter to the API structure, perhaps it is the API that should change.
I agree with you but I'm not the developer of this API. Considering how important is Control.Monad for Haskell I think it's important to pick the right name for new functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 On 21/04/14 17:47, Edward Kmett wrote:
I, for one, could get behind just taking ifM, whenM, unlessM for these operations, proper naming conventions aside.
They've been independently reinvented in 60+ packages with these exact names.
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing. This looks pragmatic now, but I, for one, think that in the future we would be appreciative of our decision to stick to conventions instead of giving in to the slippery slope of myopic pragmatism.
In any event it looks like consensus is to add these functions. Perhaps a vote thread with name options should be opened (at a later stage). - -- Alexander alexander@plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlNVPwoACgkQRtClrXBQc7X2RQD9H+3c4wR/M8pVU4km1Za0lnhH sTRLQMZkhqw3zbi0gfABAKXX1qi9HO7x2Fyb2cWbiPvFRiNCrrxVSHe8KyQkLZ72 =xR1X -----END PGP SIGNATURE-----

On Mon, Apr 21, 2014 at 11:53 AM, Alexander Berntsen
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing. This looks pragmatic now, but I, for one, think that in the future we would be appreciative of our decision to stick to conventions instead of giving in to the slippery slope of myopic pragmatism.
Descriptivism vs. prescriptivism. Somehow, prescriptivism never seems to work out in the long run; people do what they do. If they're added as mif etc., I expect those 60+ later packages will break out as 2 using the official ones and 58+ using homegrown ifM etc. still because their authors didn't notice the "weird names" ones. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I was tempted to include a linguistic example.
-ant isn't a productive suffix in English. conformant, abberant, etc. are
vestiges of a dead morphological convention.
Yet that didn't stop most of the tech industry from converging on
'performant' and using it every day, and looking at prescriptivists
strangely when they say it isn't a word. ;)
-Edward
On Mon, Apr 21, 2014 at 11:56 AM, Brandon Allbery
On Mon, Apr 21, 2014 at 11:53 AM, Alexander Berntsen
wrote:
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing. This looks pragmatic now, but I, for one, think that in the future we would be appreciative of our decision to stick to conventions instead of giving in to the slippery slope of myopic pragmatism.
Descriptivism vs. prescriptivism. Somehow, prescriptivism never seems to work out in the long run; people do what they do. If they're added as mif etc., I expect those 60+ later packages will break out as 2 using the official ones and 58+ using homegrown ifM etc. still because their authors didn't notice the "weird names" ones.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Am 21.04.2014 17:53, schrieb Alexander Berntsen:
On 21/04/14 17:47, Edward Kmett wrote:
I, for one, could get behind just taking ifM, whenM, unlessM for these operations, proper naming conventions aside.
They've been independently reinvented in 60+ packages with these exact names.
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing.
This looks pragmatic now, but I, for one, think that in the future we would be appreciative of our decision to stick to conventions instead of giving in to the slippery slope of myopic pragmatism.
I started to add monadic functions without M suffix or prefix to Control.Monad.HT module in my utility-ht package. This way I can write Monad.lift2, which is both readable and canonical. I don't see a reason why sometimes a prefix 'm' means Monoid and sometimes Monad. utility-ht is also very basic such that it can run on old GHC's and thus my packages do not need to depend in GHC-7.10 only because I like to use ifM.

On 2014-04-21 17:47, Edward Kmett wrote:
I, for one, could get behind just taking ifM, whenM, unlessM for these operations, proper naming conventions aside.
They've been independently reinvented in 60+ packages with these exact names.
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing.
+1 (for the proposal, based on exactly the above summary)

On Mon, Apr 21, 2014 at 11:19 AM, Bardur Arantsson
On 2014-04-21 17:47, Edward Kmett wrote:
I, for one, could get behind just taking ifM, whenM, unlessM for these operations, proper naming conventions aside.
They've been independently reinvented in 60+ packages with these exact names.
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing.
+1 (for the proposal, based on exactly the above summary)
+1 from me too, because I have the same functions with these names in my non-cabal packages. There might be a lot of non-cabal whenM etc. out there.

On Mon, Apr 21, 2014 at 2:26 PM, Evan Laforge
On Mon, Apr 21, 2014 at 11:19 AM, Bardur Arantsson
wrote: On 2014-04-21 17:47, Edward Kmett wrote:
I, for one, could get behind just taking ifM, whenM, unlessM for these operations, proper naming conventions aside.
They've been independently reinvented in 60+ packages with these exact names.
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing.
+1 (for the proposal, based on exactly the above summary)
+1 from me too, because I have the same functions with these names in my non-cabal packages.
There might be a lot of non-cabal whenM etc. out there.
And you're still missing a few with more specific type signatures, e.g. xmonad's whenX. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I'm +1 on whenM and unlessM - those I have wanted and think are very
worthwhile. Regardless of the naming convention stuff (which I have never
even been aware of in my day-to-day coding with Haskell), I think these are
the right names, and they also match the naming with monad-loops (`whileM`,
etc). I'd be -1 on mwhen, munless, etc.
I'm +/-0 on ifM, but that doesn't seem to be in the original proposal
anyway. I can see the value in it, but I've never really needed it. I would
probably use f >>= bool x y in practice.
- ocharles
On Mon, Apr 21, 2014 at 7:34 PM, Brandon Allbery
On Mon, Apr 21, 2014 at 2:26 PM, Evan Laforge
wrote: On Mon, Apr 21, 2014 at 11:19 AM, Bardur Arantsson
wrote: On 2014-04-21 17:47, Edward Kmett wrote:
I, for one, could get behind just taking ifM, whenM, unlessM for these operations, proper naming conventions aside.
They've been independently reinvented in 60+ packages with these exact names.
If we do this, over time we'll save another 60+ packages the trouble of doing the same thing.
+1 (for the proposal, based on exactly the above summary)
+1 from me too, because I have the same functions with these names in my non-cabal packages.
There might be a lot of non-cabal whenM etc. out there.
And you're still missing a few with more specific type signatures, e.g. xmonad's whenX.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, Apr 21, 2014 at 1:38 PM, Oliver Charles
I'm +/-0 on ifM, but that doesn't seem to be in the original proposal anyway. I can see the value in it, but I've never really needed it. I would probably use f >>= bool x y in practice.
agreed. additionally, while when/unless/whenM/unlessM gets rid of a `return ()` branch, ifM does not. In situations where I have branching code containing more than just properly curried functions I will prefer an intermediate variable if I get to use the language built-in if/then/else that gets syntax highlighted and avoids parentheses. `$ do` avoids parentheses with when/unless/whenM/unlessM, but with a second branch the parentheses return for both.

On Mon, Apr 21, 2014 at 2:55 PM, Greg Weber
agreed. additionally, while when/unless/whenM/unlessM gets rid of a `return ()` branch, ifM does not. In situations where I have branching code containing more than just properly curried functions I will prefer an intermediate variable if I get to use the language built-in if/then/else that gets syntax highlighted and avoids parentheses. `$ do` avoids parentheses with when/unless/whenM/unlessM, but with a second branch the parentheses return for both.
Looking at my own uses of 'ifM', I use it either when the branches are short: ifM ((<=) <$> Pitches.pitch_nn prev_pitch <*> Pitches.pitch_nn this_pitch) (return (Pitch.Diatonic (-1))) (return (Pitch.Diatonic 1)) ifM (Maybe.isJust <$> get) cmd_advance (cmd_set play_selected_tracks) ifM (not . wanted <$> State.get_track_title track_id) (return Nothing) (f block_id track_id events) Or when the first branch is a short exception: ifM (Directory.doesFileExist fn) (return (Just fn)) $ ifM (Directory.doesFileExist (fn ++ "c")) (return (Just (fn ++ "c"))) (return Nothing) stretch_to_1 <- ifM Internal.is_root_block (return id) $ do ) $ \omit _args deriver -> ifM (Util.chance omit) (return mempty) $ do Granted that first one is not very good.

Oliver Charles
writes:
I'm +1 on whenM and unlessM - those I have wanted and think are very worthwhile. Regardless of the naming convention stuff (which I have never even been aware of in my day-to-day coding with Haskell), I think these are the right names, and they also match the naming with monad-loops (`whileM`, etc). I'd be -1 on mwhen, munless, etc.
I completely agree with Oliver. I've wanted "whenM" more times than I can count, but mwhen doesn't feel right. +1 for whenM/unlessM, -1 for the other proposals. John

On Mon, Apr 21, 2014 at 09:49:40AM +0200, Herbert Valerio Riedel wrote:
I'm +1 on using `mif`/`mwhen`/`munless` (assuming all those pass the current naming convention), because otherwise adding an exception to the naming convention for Control.Monad entities would also require rewording the existing naming convention in the Haskell Report.
I just think that these names read horrible and also if the name 'whenM' doesn't perfectly fit into the naming convention, because 'when' already operates on Monads, nevertheless a lot of people name it 'whenM' when they need exactly this functionality, so the name doesn't seem to be completely off. But I don't think that mif/mwhen/munless is a better fit for the current naming convention, because a prefixed 'm' is mostly only used for methods of type classes.
Moreover, since 'Control.Monad' is often imported unqualified, we'd probably cause clashes in existing packages (and together with non-PVP upper-bounds on base that'd mean build failures)
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM:
These are certainly some valid points, but then I wouldn't add any new functions at all, before adding some having IMHO bad names. So I'm +1 for whenM/unlessM, but I'm not sure for IfM, because it might result into harder to read code if the 'if' and 'else' branches get longer and you have no visual hint to separate the two. Greetings, Daniel

On 2014-04-21 at 09:49:40 +0200, Herbert Valerio Riedel wrote:
On 2014-04-21 at 00:35:03 +0200, Edward Kmett wrote:
mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure.
I'm +1 on using `mif`/`mwhen`/`munless` (assuming all those pass the current naming convention), because otherwise adding an exception to the naming convention for Control.Monad entities would also require rewording the existing naming convention in the Haskell Report.
Moreover, since 'Control.Monad' is often imported unqualified, we'd probably cause clashes in existing packages (and together with non-PVP upper-bounds on base that'd mean build failures)
A quick heuristic grep over all Hackage packages results in quite a bit of packages containing the ifM/whenM/unlessM:
All that said, I'm (also) +1 the ifM/whenM/unlessM variants, under the condition that - somebody comes up with an amended wording for Haskell Report 2010's "13.2.1 Naming conventions"[3] section that avoids the inconsistency, and - somebody takes care to inform/pester/annoy the maintainers of the 70+ package that to make sure that those packages aren't left broken (if they break) for long after this gets merged into GHC HEAD [1][2] [1]: The motivation for this being, that I'd like people to be able to use nightlies of GHC HEAD, e.g. via Travis-CI to test their packages' 'master' branch early for potential GHC HEAD breakages (and report those to GHC HQ if it looks like a GHC bug), this however is thwarted if the builds start failing due to build-deps being broken. [2]: Ironically, the easiest way to fix packages (w/o breaking compat for base<4.7.1) would be to simply make sure the new ifM/whenM functions are not imported, and that the package-local hand-rolled versions of ifM/whenM are continued to be used... [3]: http://www.haskell.org/onlinereport/haskell2010/haskellch13.html#x21-1950001...

[2]: Ironically, the easiest way to fix packages (w/o breaking compat for base<4.7.1) would be to simply make sure the new ifM/whenM functions are not imported, and that the package-local hand-rolled versions of ifM/whenM are continued to be used...
Now that I'm finally confident about the approach we take for base-compat[1] (thanks to João Cristóvão for code and discussion), I want to give it more love in the future. I can add them to Control.Monad.Compat as soon as they are committed upstream and re-export the upstream versions for base > 4.7.0. That way people who are willing to depend on base-compat can just import Control.Monad.Compat. Cheers, Simon [1] http://hackage.haskell.org/package/base-compat

On Sun, Apr 20, 2014 at 6:35 PM, Edward Kmett
mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure.
The principal use of ' in base is for adding strictness, and when' and unless' don't fit that pattern. Looking at it in code doesn't send a signal that most users would pick up that an extra monadic effect is going on.
Roughly half the uses of ' in base don't involve adding strictness, by the way, and of the half that does several were added relatively recently. More accurate would probably be to say that the principal use of ' in base is for naming foldl', which I suspect originally followed the naming convention of "foo' is like foo, except different", and that the current interpretation of ' arose due to how frequently newcomers needed to be warned away from regular foldl. Using ' in this case would be historically justified but I think common consensus these days is in favor of the unwritten "foo' is like foo, except stricter" convention. - C

While the rules claim that a prefix m stands for a generalization to monadic form, in practice it is a generalization to Monoid or MonadPlus. If we look at names starting with m, we find: mplus msum mfilter All of them operate on MonadPlus. None of these functions are straightforward generalizations where arguments or results are wrapped in a monad, rather they replace addition or concatenation by the MonadPlus monoidal operation. In the base library the other names prefixed with 'm' are mappend and mconcat from Data.Monoid. Again these are monoidal operations. So to me, 'm' means "monoidal", not "monadic generalization". -1 for mif, mwhen, munless. Twan On 2014-04-21 00:35, Edward Kmett wrote:
mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure.
The principal use of ' in base is for adding strictness, and when' and unless' don't fit that pattern. Looking at it in code doesn't send a signal that most users would pick up that an extra monadic effect is going on.
-Edward
On Sun, Apr 20, 2014 at 6:22 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: when' and unless' are good names in my opinion. In Haskell libs ' is often used to define a similar function to another one.
For if' we could use the third convention. Its type is:
if :: Bool -> a -> a -> a
and by prefixing 'm' we can change it to be monadic:
mif :: (Monad m) => m Bool -> m a -> m a -> m a
that stands for monadic if. I don't like the idea of having different name notations for ifM and whenM/unlessM but that's true also for if-then-else and when/unless. I personally don't like the name 'mif' but I don't see many other solutions. Maybe the name 'if' isn't appropriate and it's better to change it into something else?
On 04/20/2014 11:48 PM, Edward Kmett wrote:
if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
mailto:ekmett@gmail.com> wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
* A postfix 'M' always stands for a function in the Kleisli category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
* A postfix '_' changes the result type from (m a) to (m ()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
* A prefix 'm' generalizes an existing function to a monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Yes, I think the stated naming conventions are somewhat off on what is
really in the module.
mfoo is generalizing foo to monads-with-extra-structure, in Control.Monad
at least.
But fooM is generally about functions that 'sequence' multiple actions. For
instance:
mapM f = sequence . map f
This also explains replicateM, as:
replicateM n = sequence . replicate n
And liftM through liftM5 are similar.
ifM, whenM, unlessM, etc. do not involve monads with extra structure, but
they are about sequencing extra monadic stuff, which seems to be what the M
suffix is actually about. So they seem like the better names.
-- Dan
On Mon, Apr 21, 2014 at 11:16 AM, Twan van Laarhoven
While the rules claim that a prefix m stands for a generalization to monadic form, in practice it is a generalization to Monoid or MonadPlus. If we look at names starting with m, we find:
mplus msum mfilter
All of them operate on MonadPlus. None of these functions are straightforward generalizations where arguments or results are wrapped in a monad, rather they replace addition or concatenation by the MonadPlus monoidal operation.
In the base library the other names prefixed with 'm' are mappend and mconcat from Data.Monoid. Again these are monoidal operations. So to me, 'm' means "monoidal", not "monadic generalization".
-1 for mif, mwhen, munless.
Twan
On 2014-04-21 00:35, Edward Kmett wrote:
mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure.
The principal use of ' in base is for adding strictness, and when' and unless' don't fit that pattern. Looking at it in code doesn't send a signal that most users would pick up that an extra monadic effect is going on.
-Edward
On Sun, Apr 20, 2014 at 6:22 PM, Mario Pastorelli < pastorelli.mario@gmail.com mailto:pastorelli.mario@gmail.com> wrote:
when' and unless' are good names in my opinion. In Haskell libs ' is often used to define a similar function to another one.
For if' we could use the third convention. Its type is:
if :: Bool -> a -> a -> a
and by prefixing 'm' we can change it to be monadic:
mif :: (Monad m) => m Bool -> m a -> m a -> m a
that stands for monadic if. I don't like the idea of having different name notations for ifM and whenM/unlessM but that's true also for if-then-else and when/unless. I personally don't like the name 'mif' but I don't see many other solutions. Maybe the name 'if' isn't appropriate and it's better to change it into something else?
On 04/20/2014 11:48 PM, Edward Kmett wrote:
if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote:
My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
mailto:ekmett@gmail.com> wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
* A postfix 'M' always stands for a function in the Kleisli
category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
* A postfix '_' changes the result type from (m a) to (m
()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
* A prefix 'm' generalizes an existing function to a
monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli
> wrote:
Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ 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

All of the current fooM functions only need Applicative, and might over time be renamed to fooA. Similarly all current mfoo functions only need Alternative, and should be called afoo.
So imho we’re free to choose a new naming scheme, and ifM, whenM and unlessM would be the first to truly live up to their postfix.
Sjoerd
On 21 Apr 2014, at 18:01, Dan Doel
Yes, I think the stated naming conventions are somewhat off on what is really in the module.
mfoo is generalizing foo to monads-with-extra-structure, in Control.Monad at least.
But fooM is generally about functions that 'sequence' multiple actions. For instance:
mapM f = sequence . map f
This also explains replicateM, as:
replicateM n = sequence . replicate n
And liftM through liftM5 are similar.
ifM, whenM, unlessM, etc. do not involve monads with extra structure, but they are about sequencing extra monadic stuff, which seems to be what the M suffix is actually about. So they seem like the better names.
-- Dan
On Mon, Apr 21, 2014 at 11:16 AM, Twan van Laarhoven
wrote: While the rules claim that a prefix m stands for a generalization to monadic form, in practice it is a generalization to Monoid or MonadPlus. If we look at names starting with m, we find: mplus msum mfilter
All of them operate on MonadPlus. None of these functions are straightforward generalizations where arguments or results are wrapped in a monad, rather they replace addition or concatenation by the MonadPlus monoidal operation.
In the base library the other names prefixed with 'm' are mappend and mconcat from Data.Monoid. Again these are monoidal operations. So to me, 'm' means "monoidal", not "monadic generalization".
-1 for mif, mwhen, munless.
Twan
On 2014-04-21 00:35, Edward Kmett wrote: mif appears to pass the naming convention rules. It looks strange, but we can chalk that up to lack of exposure.
The principal use of ' in base is for adding strictness, and when' and unless' don't fit that pattern. Looking at it in code doesn't send a signal that most users would pick up that an extra monadic effect is going on.
-Edward
On Sun, Apr 20, 2014 at 6:22 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: when' and unless' are good names in my opinion. In Haskell libs ' is often used to define a similar function to another one.
For if' we could use the third convention. Its type is:
if :: Bool -> a -> a -> a
and by prefixing 'm' we can change it to be monadic:
mif :: (Monad m) => m Bool -> m a -> m a -> m a
that stands for monadic if. I don't like the idea of having different name notations for ifM and whenM/unlessM but that's true also for if-then-else and when/unless. I personally don't like the name 'mif' but I don't see many other solutions. Maybe the name 'if' isn't appropriate and it's better to change it into something else?
On 04/20/2014 11:48 PM, Edward Kmett wrote: if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
On Sun, Apr 20, 2014 at 5:45 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote: I see. Another solution is to use if', when' and unless'.
On 04/20/2014 11:42 PM, Edward Kmett wrote: My mistake. These rules are still in Control.Monad. I just scrolled right past them.
-Edward
On Sun, Apr 20, 2014 at 5:04 PM, Edward Kmett
mailto:ekmett@gmail.com> wrote: The principled objection to giving these combinators the "obvious" names in Control.Monad is that that module has historically held to a detailed convention that these proposed names unfortunately don't fit. =/
The functions in this library use the following naming conventions:
* A postfix 'M' always stands for a function in the Kleisli
category: The monad type constructor m is added to function results (modulo currying) and nowhere else. So, for example,
filter :: (a -> Bool) -> [a] -> [a] filterM :: (Monad m) => (a -> m Bool) -> [a] -> m [a]
* A postfix '_' changes the result type from (m a) to (m
()). Thus, for example:
sequence :: Monad m => [m a] -> m [a] sequence_ :: Monad m => [m a] -> m ()
* A prefix 'm' generalizes an existing function to a
monadic form. Thus, for example:
sum :: Num a => [a] -> a msum :: MonadPlus m => [m a] -> m a
That said, if we do adopt them, they probably should get the ifM, whenM, unlessM names.
I don't think the convention has been documented in Control.Monad itself for years.
-Edward
On Sun, Apr 20, 2014 at 4:26 PM, Mario Pastorelli
mailto:pastorelli.mario@gmail.com> wrote:
Hi Herbert,
in general I like pattern matching but not when boolean values are involved. Your code is nice but, in my opinion, still far from the elegance of
f = unlessM (doesDirectoryExist path) $ do
putStrLn $ "Creating directory " ++ path createDirectory path
In particular, note that I don't have to take care of the False case and the code doesn't have boilerplate.
While your solution is more general, I would like to point out that when and unless are so useful that they got their own functions in the library instead of relying on pattern matching. I consider ifM, whenM and unlessM as alternate versions of existing functions.
On 04/20/2014 09:59 PM, Herbert Valerio Riedel wrote:
Hi Mario,
On 2014-04-20 at 21:10:03 +0200, Mario Pastorelli wrote:
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 ()
[...]
f = do dirDoesntExist <- not <$> doesDirectoryExist path when dirDoesntExist $ do putStrLn $ "Creating directory " ++ path createDirectory path
While I'm neutral on this proposal, I'd like to remind that LambdaCase may be useful to avoid temporary variables as well (and is even more useful for types other than Bool):
f = doesDirectoryExist path >>= \case True -> return () False -> do putStrLn $ "Creating directory " ++ path createDirectory path Cheers, hvr
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ 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
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Mon, Apr 21, 2014 at 12:01 PM, Dan Doel
Yes, I think the stated naming conventions are somewhat off on what is really in the module.
mfoo is generalizing foo to monads-with-extra-structure, in Control.Monad at least.
But fooM is generally about functions that 'sequence' multiple actions. For instance:
mapM f = sequence . map f
This also explains replicateM, as:
replicateM n = sequence . replicate n
And liftM through liftM5 are similar.
ifM, whenM, unlessM, etc. do not involve monads with extra structure, but they are about sequencing extra monadic stuff, which seems to be what the M suffix is actually about. So they seem like the better names.
I would actually say that the M suffix is primarily used to indicate that sequential control flow is involved. In Control.Monad that amounts to very simple loop-like constructs, but in other code the fooM convention seems to appear most often on functions that want to do something to a data structure while binding only those monadic values corresponding to constructors that would be created/evaluated in the pure version. Thus why the M prefix is so commonly used when reinventing simple conditional statements. Not sure how that would apply to liftM & co., though. - C.

On 2014-04-20 at 23:48:06 +0200, Edward Kmett wrote:
if' is a commonly used name in user code for what is now called bool, but it also gets used all over the place for 'if' inside of EDSLs.
Just a minor nit-pick, I had always assumed if' and bool had different argument ordering: bool :: a -> a -> Bool -> a bool f _ False = f bool _ t True = t (following the style of 'either'/'maybe') vs. if' :: Bool -> a -> a -> a if' True x _ = x if' False _ y = y (see http://www.haskell.org/haskellwiki/If-then-else)

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 - -1 from me. But "if you must", I would prefer m-prefix to M-suffix, to keep things consistent. If we start breaking those conventions, things get messy, and I can't reliably predict what a function that deals with monads does any longer, except for "it does something which involves monads at some stage". - -- Alexander alexander@plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlNVCagACgkQRtClrXBQc7Xl0wD/ff1f8W9k83fuB8MPgHFVE2fw hubCbjtUFXE2uB+8epMA/02cQRDxftkKJ/9dI7dNYr+bGkwAM2si4xVnmsY+dONy =n1K/ -----END PGP SIGNATURE-----

Here are my official votes: +1 for whenM/unlessM indifferent on ifM -1 for mwhen/munless/mif Cheers, Simon

On 2014-04-20 20:10, Mario Pastorelli wrote:
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 ()
Here's my vote, +1 for whenM and unlessM. not a big fan of ifM otherwise, but i'll remain neutral about it. -- Vincent
participants (24)
-
Alexander Berntsen
-
Alois Cochard
-
Andreas Abel
-
Bardur Arantsson
-
Brandon Allbery
-
Carter Schonwald
-
Casey McCann
-
Dan Doel
-
Daniel Trstenjak
-
David Mazieres
-
Edward Kmett
-
Evan Laforge
-
Greg Weber
-
Henning Thielemann
-
Herbert Valerio Riedel
-
John Wiegley
-
Mario Pastorelli
-
Oliver Charles
-
Simon Hengel
-
Sjoerd Visscher
-
Tom Ellis
-
Twan van Laarhoven
-
Vincent Hanquez
-
wren romano