Monoid

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

In Haskell, the Monoid typeclass (not to be confused with Monad) is a class for types which have a single most natural operation for combining values, together with a value which doesn't do anything when you combine it with others (this is called the identity element). It is closely related to the Foldable class, and indeed you can think of a Monoid instance declaration for a type m as precisely what you need in order to fold up a list of values of m.

The basics

Declaration

class Semigroup m where
  (<>) :: m -> m -> m

  -- defining sconcat is unnecessary, it has a default implementation
  sconcat :: NonEmpty m -> m
  sconcat = ...

  -- defining stimes is unnecessary, it has a default implementation
  stimes :: Integral a => a -> m -> m
  stimes = ...

infixr 6 <>

class Semigroup m => Monoid m where
  mempty :: m

  -- defining mappend is unnecessary, it copies from Semigroup
  mappend :: m -> m -> m
  mappend = (<>)

  -- defining mconcat is optional, since it has the following default:
  mconcat :: [m] -> m
  mconcat = foldr mappend mempty

together with the following laws:

-- Identity laws
x <> mempty = x
mempty <> x = x

-- Associativity
(x <> y) <> z = x <> (y <> z)

Examples

The prototypical and perhaps most important example is lists, which form a monoid under concatenation:

instance Semigroup [a] where
  (<>) = (++)

instance Monoid [a] where
  mempty = []

Indeed, appending the empty list to either end of an existing list does nothing, and (x ++ y) ++ z and x ++ (y ++ z) are both the same list, namely all the elements of x, then all the elements of y, them all the elements of z.

Numbers also form a monoid under addition, with 0 the identity element, but they also form a monoid under multiplication, with 1 the identity element. Neither of these instances are really more natural than the other, so we use the newtypes Sum n and Product n to distinguish between them:

newtype Sum n = Sum n

instance Num n => Semigroup (Sum n) where
  Sum x <> Sum y = Sum (x + y)

instance Num n => Monoid (Sum n) where
  mempty = Sum 0

newtype Product n = Product n

instance Num n => Semigroup (Product n) where
  Product x <> Product y = Product (x * y)

instance Num n => Monoid (Product n) where
  mempty = Product 1

Now mconcat on a list of Sum Integer (say) values works like sum, while on a list of Product Double values it works like product.

So what?

There are several reasons why you want a typeclass for combining things, e.g. because it couples well with other typeclasses (the aforementioned Foldable, or the Writer monad, or some Applicatives). But for a rather striking example of what Monoid can do alone, you can look at the way its instances can work together. First, Ordering, the standard type which Haskell uses for the result of compare functions, has a "lexicographic" combination operation, where mappend essentially takes the first non-equality result. Secondly, if b is a Monoid, then functions of type a -> b can be combined by just calling them both and combining the results. Now, of course, since a -> a -> b is just a function returning a function, it can also be combined in the same way, and so you can combine comparison functions, of type a -> a -> Ordering, and write the following sorts of thing, which means "sort strings by length and then alphabetically":

sortStrings = sortBy (comparing length <> compare)

Isn't that wonderfully descriptive? And we didn't write any functions specifically to do this – it's just composed of simple, reusable parts.

In more depth

On mconcat

mconcat is often presented as just an optimisation, only in the class so that people can define more efficient versions of it. That's true in a sense, but note that mempty and mappend can just as well be defined in terms of mconcat:

mempty = mconcat []
mappend x y = mconcat [x, y]

What of the laws? Well, we can have the following:

mconcat [x] = x
mconcat (map mconcat xss) = mconcat (concat xss)

The first rule is natural enough. The second rule is a little more subtle, but basically says that if you have a list of lists of some monoidy things, and you mconcat each sublist individually, then mconcat all the results, that's just the same as if you had squashed all the sublists together first, and mconcatted the result of that. Or in other words, it's telling you something like what associativity tells you, that the order in which you fold up a list doesn't matter.

Categorical diversion

Note that the above two laws can also be phrased as follows:

mconcat . return = id
mconcat . map mconcat = mconcat . join

In category theory terms, this is exactly the condition for mconcat to be a monad algebra for the list monad.

On the Writer monad

The Writer monad is a way to put a monad structure on tuples. You write bind like this:

(w,x) >>= f =
  case f x of
    (v, y) -> (w <> v, y)

Notice that it's the monoid instance of the first component that allows you to incorporate both w and v into the final result, which seems like an important thing to do.

You might, however, wonder if there's not some other way to get a law-abiding monad. The answer is essentially no: if (w,a) is a monad, you can use its monad instance to write a monoid instance for w: basically mempty = fst (return ()) and mappend x y = fst (join (x,(y,())), and the monad laws ensure associativity and identity. So in fact, monoids are exactly what you need to make a monad structure on tuples.

On the Const applicative

Even more straightforwardly, Const m is applicative precisely when m is a monoid.

See also

Generalizations of monoids feature in Category theory, for example: