Monoid vs MonadPlus

If we have that MonadPlus m holds then you'd say m is a Monad, but m a (the type resulting from applying a to the type "function" m) is a monoid.

If we define (similar to Data.Monoid's definition, but we'll make use of this later)

class                Semigroup a where  (<>) :: a -> a -> a
class Semigroup a => Monoid    a where  zero :: a

then it has

mzero :: MonadPlus m => m a
mplus :: MonadPlus m => m a -> m a -> m a

with pretty comparable types and the apropriate laws

-- left and right identity
mplus a     mzero   ==   a
mplus mzero a       ==   a

-- associativity
(a `mplus` b) `mplus` c   ==   a `mplus` (b `mplus` c)

We can even define a Haskell Monoid if we use -XFlexibleInstances

{-# LANGUAGE FlexibleInstances #-}
instance MonadPlus m => Semigroup (m a) where  (<>) = mplus
instance MonadPlus m => Monoid    (m a) where  zero = mzero

though these overlap badly with the instances in Data.Monoid, which is probably why it isn't a standard instance.


Another example of a monoid like this is Alternative m => m a from Control.Applicative.


A semigroup is a structure equipped with an associative binary operation. A monoid is a semigroup with an identity element for the binary operation.

Monads and semigroups

Every monad has to adhere to the monad laws. For our case, the important one is the associativity law. Expressed using >>=:

(m >>= f) >>= g     ≡   m >>= (\x -> f x >>= g)

Now let's apply this law to deduce the associativity for >> :: m a -> m b -> m b:

(m >> n) >> p       ≡ (m >>= \_ -> n) >>= \_ -> p
                    ≡ m >>= (\x -> (\_ -> n) x >>= \_ -> p)
                    ≡ m >>= (\x -> n >>= \_ -> p)
                    ≡ m >>= (\x -> n >> p)
                    ≡ m >> (n >> p)

(where we picked x so that it doesn't appear in m, n or p).

If we specialize >> to the type m a -> m a -> m a (substituting b for a), we see that for any type a the operation >> forms a semigroup on m a. Since it's true for any a, we get a class of semigroups indexed by a. However, they are not monoids in general - we don't have an identity element for >>.

MonadPlus and monoids

MonadPlus adds two more operations, mplus and mzero. MonadPlus laws state explicitly that mplus and mzero must form a monoid on m a for an arbitrary a. So again, we get a class of monoids indexed by a.

Note the difference between MonadPlus and Monoid: Monoid says that some single type satisfies the monoidal rules, while MonadPlus says that for all possible a the type m a satisfies the monoidal laws. This is a much stronger condition.

So a MonadPlus instance forms two different algebraic structures: A class of semigroups with >> and a class of monoids with mplus and mzero. (This is not something uncommon, for example the set of natural numbers greater than zero {1,2,...} forms a semigroup with + and a monoid with × and 1.)