[Haskell-cafe] replicateM should be called mreplicate?

David Menendez dave at zednenem.com
Mon Apr 6 13:42:31 EDT 2009


On Mon, Apr 6, 2009 at 10:02 AM, Sjoerd Visscher <sjoerd at w3future.com> wrote:
> 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 <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list