Proposal: add ifM and whenM to Control.Monad

Edward Kmett ekmett at gmail.com
Sun Apr 20 21:42:58 UTC 2014


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 <ekmett at 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 <
> pastorelli.mario at 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20140420/079ece15/attachment-0001.html>


More information about the Libraries mailing list