replicateM should be called mreplicate?

Considering these naming conventions: http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html#3 • 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 replicateM has the following type: replicateM :: Monad m => Int -> m a -> m [a] Am I missing something or should this have been called mreplicate? greetings, -- Sjoerd Visscher sjoerd@w3future.com

On Mon, Apr 6, 2009 at 10:02 AM, Sjoerd Visscher
Considering these naming conventions: http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html#3
• 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
replicateM has the following type:
replicateM :: Monad m => Int -> m a -> m [a]
Am I missing something or should this have been called mreplicate?
Not necessarily. If you use replicateM in the identity monad, you get
replicate. Similarly with filterM and filter, or foldM and foldl.
In contrast, msum and sum are essentially mconcat specialized to the
monoids (mplus, mzero) and ((+), 0), respectively.
Of course, this suggests that mfix should be fixM, so perhaps a better
distinction is that mplus and mfix need to be defined per-monad,
whereas filterM and replicateM are generic.
--
Dave Menendez

On Mon, Apr 6, 2009 at 11:42 AM, David Menendez
Of course, this suggests that mfix should be fixM, so perhaps a better distinction is that mplus and mfix need to be defined per-monad, whereas filterM and replicateM are generic.
Don't you think that is an incidental distinction, not an essential one? It would be like naming our favorite operations mbind and joinM, just because of the way we happened to write the monad class. Luke
-- Dave Menendez
<http://www.eyrie.org/~zednenem/ http://www.eyrie.org/%7Ezednenem/> _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Apr 6, 2009 at 1:46 PM, Luke Palmer
On Mon, Apr 6, 2009 at 11:42 AM, David Menendez
wrote: Of course, this suggests that mfix should be fixM, so perhaps a better distinction is that mplus and mfix need to be defined per-monad, whereas filterM and replicateM are generic.
Don't you think that is an incidental distinction, not an essential one? It would be like naming our favorite operations mbind and joinM, just because of the way we happened to write the monad class.
Fair enough. I only added that comment when I noticed that my
explanation for picking replicateM over mreplicate also applied to
mfix.
Looking through Control.Monad, I see that all the *M functions require
Monad, whereas the m* functions require MonadPlus (or MonadFix). I
wonder to what extent that pattern holds in other libraries?
--
Dave Menendez

On 7 Apr 2009, at 07:37, David Menendez wrote:
On Mon, Apr 6, 2009 at 1:46 PM, Luke Palmer
wrote: On Mon, Apr 6, 2009 at 11:42 AM, David Menendez
wrote: Of course, this suggests that mfix should be fixM, so perhaps a better distinction is that mplus and mfix need to be defined per-monad, whereas filterM and replicateM are generic.
Don't you think that is an incidental distinction, not an essential one? It would be like naming our favorite operations mbind and joinM, just because of the way we happened to write the monad class.
Fair enough. I only added that comment when I noticed that my explanation for picking replicateM over mreplicate also applied to mfix.
Looking through Control.Monad, I see that all the *M functions require Monad, whereas the m* functions require MonadPlus (or MonadFix).
Actually, most of the *M functions only require Applicative – they're just written in a time when that wasn't in the libraries.
I wonder to what extent that pattern holds in other libraries?
I'm not sure how to generalise this pattern, but it's probably worth noting that fmap is fmap, not mapF. I can't see any pattern that it fits into, really I suspect it's a case of "what shall we name this" and not enough thought about consistant naming as the libraries evolved. Bob
participants (4)
-
David Menendez
-
Luke Palmer
-
Sjoerd Visscher
-
Thomas Davie