The unfortunate meme phrase “a monad is just a monoid in the category of endofunctors, what’s the problem?” comes from two sources:
The meme words have become an annoying blot on the fringes of the Haskell universe. Learning resources don’t mention it, the core Haskell community doesn’t like it because it adds little and spooks newcomers, and it’s completely unnecessary to understand it if you just want to write Haskell code. But it is interesting, and it pops up in enough cross-language programming communities that there’s still a lot of curiosity about the meme words. I wrote an explanation on reddit recently, it became my highest-voted comment overnight, and someone said that it deserved its own blog post. This is that post.
This is not a monad tutorial. You do not need to read this, especially if you’re new to Haskell. Do something more useful with your time. But if you will not be satisfied until you understand the meme words, let’s proceed. I’ll assume knowledge of categories, functors, and natural transformations.
“A monad is a monoid in the category of endofunctors” is not specific enough. Let’s fill in the details and specialise it to Haskell monads, so that we build towards a familiar typeclass:
“Haskell monads are monoid objects in the monoidal category of endofunctors on Hask, with functor composition as the tensor.”
Let’s first practice looking for monoid objects in a monoidal category that’s very familiar to Haskell programmers: Hask, the “category” where the objects are Haskell types and the morphisms are functions between the types. (I use scare quotes because we quietly ignore ⊥).
We will first explore the following simpler claim about monoids, and come back to monads:
“Haskell monoids are monoid objects in the monoidal
category Hask, with
(,)
as the tensor.”
We will need the categorical definition of bifunctors to define monoidal categories, and we’ll need product categories to define bifunctors:
Definition 1: The product of two categories is called a product category. If C and D are categories, their product is written C × D and is a category where:
Definition 2: A bifunctor is a functor whose domain is a product category.
In Haskell, we tend to only think about bifunctors Hask × Hask → Hask,
as represented by class Bifunctor
:
class (forall a. Functor (p a)) => Bifunctor p where
bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
-- other methods omitted
-- Uncurrying bimap and adding parens for clarity:
bimap' :: Bifunctor p => (a -> b, c -> d) -> (p a c -> p b d)
= bimap f g p bimap' (f, g) p
bimap
and bimap'
are equivalent, and you
can see how bimap'
maps a morphism from Hask × Hask
to a morphism in Hask.
We use bimap
because it is more ergonomic to program
with.
Aside 3: Iceland_Jack
has an unofficial plan to unify the various functor typeclasses
using a general categorical interface, which has the potential to
subsume a lot of ad-hoc typeclasses. If done in a backwards-compatible
way, it would be extremely cool.
Exercise 4: Show that Either
is a
bifunctor on Hask × Hask → Hask,
by giving it a Bifunctor
instance.
{-# LANGUAGE InstanceSigs #-}
instance Functor (Either x) where
fmap :: (a -> b) -> Either x a -> Either x b
fmap _ (Left x) = Left x
fmap f (Right a) = Right (f a)
instance Bifunctor Either where
bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d
Left a) = Left (f a)
bimap f _ (Right b) = Right (g b) bimap _ g (
Exercise 5: Show that (,)
is a
bifunctor on Hask × Hask → Hask,
by giving it a Bifunctor
instance.
{-# LANGUAGE InstanceSigs #-}
instance Functor ((,) x) where
fmap :: (a -> b) -> (x, a) -> (x, b)
fmap f (x, a) = (x, f a)
instance Bifunctor (,) where
bimap :: (a -> b) -> (c -> d) -> (a, b) -> (c, d)
= (f a, g b) bimap f g (a, b)
The definition of monoidal category also relies on the definition of natural isomorphism, so let’s define and discuss them.
Definition 6: If F and G are functors from C to D, a natural isomorphism is a natural transformation η : F ⇒ G where η is an isomorphism for every object c in C.
If you are used to the Haskell definition of “natural transformation”, you might be wondering what this “for every object” business is about:
{-# LANGUAGE RankNTypes, TypeOperators #-}
type f ~> g = forall a. f a -> g a
In Haskell, we use parametrically-polymorphic functions as natural
transformations between endofunctors on Hask. This is a stronger
condition than the categorical definition requires, where a natural
transformation is a collection of morphisms in the target
category, indexed by objects in the source category. The
equivalent in Haskell would be like being able to choose one function
for f Int -> g Int
and another for
f Bool -> g Bool
(subject to conditions).
I have been told that internalising the Haskell version of natural transformations may leave you unable to prove certain results in category theory, but I don’t know which ones. I know that it’s because you may find yourself trying to construct a parametrically-polymorphic function instead of just a natural transformation.
For today’s purposes, we can say that
nt :: f a -> g a
is a natural isomorphism if it has an
inverse unnt :: g a -> f a
.
Counter-Example 7:
listToMaybe :: [a] -> Maybe a
is a natural
transformation but not a natural isomorphism, because it is not
invertible.
We are now ready to define monoidal categories.
Definition 8: A monoidal category is a triple (C, ⊗, I) where:
C is a category;
⊗ is a bifunctor C × C → C called the tensor product;
I is an object of C called the identity object;
Natural isomorphisms and coherence conditions showing that ⊗ is associative and has and I is its left and right identity:
α : − ⊗ (−⊗−) ⇒ (−⊗−) ⊗ −, standing for αssociator, with components αA, B, C : A ⊗ (B⊗C) ≅ (A⊗B) ⊗ C;
( − ⊗ (−⊗−) means the functor that takes C to C × (C × C).)
λ : 1C ⇒ (I⊗−), standing for λeft unitor, with components λA : A ≅ I ⊗ A;
(1C is the identity functor on C.)
ρ : 1C ⇒ (−⊗I), standing for ρight unitor, with components ρA : A ≅ A ⊗ I; and
The coherence conditions have nice diagrams at the Wikipedia definition.
We can now say that (Hask, (,)
,
()
) is a monoidal category:
Hask is a “category”;
(,)
has a Bifunctor
instance, so it’s a
bifunctor from Hask × Hask → Hask;
()
is a type, so it is an object in Hask;
We can write parametric functions to demonstrate the natural isomorphisms (the coherence conditions come for free, from parametricity):
assoc :: (a, (b, c)) -> ((a, b), c)
unassoc :: ((a, b), c) -> (a, (b, c))
left :: a -> ((), a)
unleft :: ((), a) -> a
right :: a -> (a, ())
unright :: (a, ()) -> a
Exercise 9: Implement these natural isomorphisms.
assoc :: (a, (b, c)) -> ((a, b), c)
= ((a, b), c)
assoc (a, (b, c))
unassoc :: ((a, b), c) -> (a, (b, c))
= (a, (b, c))
unassoc ((a, b), c)
left :: a -> ((), a)
= ((), a)
left a
unleft :: ((), a) -> a
= a
unleft ((), a)
right :: a -> (a, ())
= (a, ())
right a
unright :: (a, ()) -> a
= a unright (a, ())
Exercise 10: Show that (Hask, Either
,
Void
) is a monoidal category.
Hask is a “category”;
Either
has a Bifunctor
instance, so
it’s a bifunctor from Hask × Hask → Hask;
Void
is a type, so it is an object in Hask;
We can write parametric functions to demonstrate the natural isomorphisms (the coherence conditions come for free, from parametricity):
import Data.Void
assoc :: Either a (Either b c) -> Either (Either a b) c
Left a) = Left (Left a)
assoc (Right (Left b)) = Left (Right b)
assoc (Right (Right c)) = Right c
assoc (
unassoc :: Either (Either a b) c -> Either a (Either b c)
Left (Left a)) = Left a
unassoc (Left (Right b)) = Right (Left b)
unassoc (Right c) = Right (Right c)
unassoc (
left :: a -> Either Void a
= Right -- It puts the identity (Void) on the left
left
unleft :: Either Void a -> a
Left v) = absurd v
unleft (Right a = a
unleft
right :: a -> Either a Void
= Left
right
unright :: Either a Void -> a
Left a) = a
unright (Right v) = absurd v unright (
Remark: The assoc
package defines class Bifunctor p => Assoc p
, with
assoc
/unassoc
methods.
Now that we have some monoidal categories, we can go looking for monoid objects. Let’s define them:
Definition 11: A monoid object in a monoidal category (C, ⊗, I) is a triple (M, μ, η) where:
What are the monoid objects in the monoidal category (Hask, (,)
,
()
)? To associate morphisms (functions) with an object
(type), we use a typeclass; the type variable m
identifies
M, and the rest is
substitution:
class MonoidObject m where
mu :: (m, m) -> m
eta :: () -> m
If you squint, you might be able to see why this is
class Monoid
in disguise: mu
is uncurried
(<>)
, and eta
is mempty
(laziness makes m
equivalent to the function
() -> m
).
Either
,
Void
)?
2023-02-10 EDIT: The previous solution here was wrong, and has been replaced. Thanks to James Cranch for the correction.
In any cocartesian monoidal category (i.e., a category using the coproduct as the tensor), every object is a monoid object in a boring way. To see this in Hask, write out the class and instance definitions:
class MonoidObjectE m where
mu :: Either m m -> m
eta :: Void -> m
instance MonoidObjectE m where
= either id id
mu = absurd eta
Hask
Now we will do it all again, starting with the category of endofunctors on Hask. This category is sometimes written HaskHask, because of the connection between functions a → b and exponentials ba. Since we don’t have to set up all the definitions, we can move faster. We describe a category by identifying its objects and its morphisms, so for HaskHask:
To turn HaskHask into a monoidal category, we need to consider bifunctors from HaskHask × HaskHask to HaskHask, and to do that, we need to consider what a functor from HaskHask to HaskHask would look like.
A functor sends objects to objects and morphisms to morphisms, and
for the sake of analogy let’s look back on functors from Hask to Hask. As Haskell
programmers, we represent them with type constructors of kind
Type -> Type
to fit our chosen domain and codomain, and
we use a typeclass to map morphisms (functions):
-- The one from `base`, plus a kind annotation:
class Functor (f :: Type -> Type) where
-- Parens added for clarity
fmap :: (a -> b) -> (f a -> f b)
So for endofunctors on HaskHask,
we need a type constructor that turns an argument of kind
(Type -> Type)
into (Type -> Type)
. This
means we need an alternate version of class Functor
:
class Functor2 (t :: (Type -> Type) -> (Type -> Type)) where
fmap2 :: (forall x. f x -> g x) -> (t f a -> t g a)
Remark: This is very close to class MFunctor
from package mmorph
, but MFunctor
identifies functors on the category of Haskell monads, which is a
stricter condition.
Similarly, we will need to identify bifunctors from HaskHask × HaskHask
to HaskHask,
with an alternate version of class Bifunctor
:
class (forall f. Functor2 (t f)) =>
Bifunctor2 (t :: (Type -> Type) -> (Type -> Type) -> (Type -> Type)) where
bimap2 ::
forall x. p x -> q x) ->
(forall x. r x -> s x) ->
(-> t q s a) (t p r a
So we need to find monoid objects in a monoidal category of endofunctors. That means we need to identify a bifunctor and identity object for our monoidal category. We will use functor composition as our tensor and the identity functor as our identity object:
-- From Data.Functor.Compose in base
newtype Compose f g a = Compose { getCompose :: f (g a) }
-- From Data.Functor.Identity in base
newtype Identity a = Identity { runIdentity :: a }
Exercise 13: Show that the composition of two
functors is a functor, by writing
instance (Functor f, Functor g) => Functor (Compose f g)
instance (Functor f, Functor g) => Functor (Compose f g) where
fmap f = Compose . (fmap . fmap) f . getCompose
Exercise 14: Show that Compose
is a
bifunctor from HaskHask
to itself by writing Functor2
and Bifunctor2
instances.
instance Functor x => Functor2 (Compose x) where
= Compose . fmap fg . getCompose
fmap2 fg
instance (forall x. Functor2 (Compose x)) => Bifunctor2 Compose where
= Compose . pq . getCompose . fmap2 rs bimap2 pq rs
Exercise 15: Write out and implement the natural
isomorphisms, showing that (HaskHask,
Compose
, Identity
) is a monoidal category.
assoc :: Functor f => Compose f (Compose g h) a -> Compose (Compose f g) h a
= Compose . Compose . fmap getCompose . getCompose
assoc
unassoc :: Functor f => Compose (Compose f g) h a -> Compose f (Compose g h) a
= Compose . fmap Compose . getCompose . getCompose
unassoc
left :: f a -> Compose Identity f a
= Compose . Identity
left
unleft :: Compose Identity f a -> f a
= runIdentity . getCompose
unleft
right :: Functor f => f a -> Compose f Identity a
= Compose . fmap Identity
right
unright :: Functor f => Compose f Identity a -> f a
= fmap runIdentity . getCompose unright
We are now ready to answer the question posed by the meme words: what
are the monoid objects in the monoidal category (HaskHask,
Compose
, Identity
)?
The monoid objects are objects in HaskHask,
so they are functors; we will write our typeclass with a
Functor
superclass constraint. mu
is a natural
transformation from Compose m m
to m
, and
eta
is a natural transformation from Identity
to m
:
class Functor m => MonoidInTheCategoryOfEndofunctors m where
mu :: Compose m m a -> m a
eta :: Identity a -> m a
If we unwrap the newtypes, we see that eta
is
effectively
eta' :: MonoidInTheCategoryOfEndofunctors m => a -> m a
,
which is pure
from class Applicative
as well
as the old return
from class Monad
. Similarly,
mu
is effectively
mu' :: MonoidInTheCategoryOfEndofunctors m => m (m a) -> m a
,
better known as
join :: Monad m => m (m a) -> m a
.
And there we have it: Haskell’s monads are the monoid objects in the
monoidal category of endofunctors on Hask, with
Compose
as the tensor. Haskell uses
(>>=)
in class Monad
for historical
reasons, and because having join
in
class Monad
breaks
-XGeneralizedNewtypeDeriving
.
Exercise 16: Show that join
and
(>>=)
are equivalent, by implementing them in terms
of each other.
join :: Monad m => m (m a) -> m a
= (>>= id)
join
(>>=) :: Monad m => m a -> (a -> m b) -> m b
>>= f = join $ f <$> m m
Now that we’ve looked at the meme words properly, we see that the selection of tensor is extremely important. What happens if we choose a different one?
Exercise 17: Consider the tensor
newtype Product f g a = Product (f a) (g a)
, from Data.Functor.Product
in base
. What is the identity object I that makes (HaskHask,
Product
, I) a
monoidal category? Write out the types and implement the natural
isomorphisms assoc
, left
, and
right
, and describe the monoid objects in this
category.
The identity object is Proxy
, defined
in base
:
data Proxy a = Proxy
Proxy
plays a similar role to ()
— we don’t
want to add or remove any information when we write out the unitors, and
you can think of Proxy
as a functor
containing zero “a
”s.
instance Functor2 (Product x) where
Product x f) = Product x (fg f)
fmap2 fg (
instance (forall x. Functor2 (Product x)) => Bifunctor2 Product where
Product p r) = Product (pq p) (rs r)
bimap2 pq rs (
assoc :: Product f (Product g h) a -> Product (Product f g) h a
Product f (Product g h)) = Product (Product f g) h
assoc (
unassoc :: Product (Product f g) h a -> Product f (Product g h) a
Product (Product f g) h) = Product f (Product g h)
unassoc (
left :: f a -> Product Proxy f a
= Product Proxy f
left f
unleft :: Product Proxy f a -> f a
Product _ f) = f
unleft (
right :: f a -> Product f Proxy a
= Product f Proxy
right f
unright :: Product f Proxy a -> f a
Product f _) = f unright (
As before, the requirements on monoid objects lead us to write a typeclass:
class Functor m => MonoidObject (m :: Type -> Type) where
eta :: Proxy a -> m a
mu :: Product m m a -> m a
Proxy
argument to eta
contains no
information, so it’s equivalent to zero :: m a
. By
unpacking Product m m a
and currying mu
, we
find (<!>) :: m a -> m a -> m a
. We have
rediscovered class Plus
from semigroupoids
. (It is not class Alternative
from base
, because that has an Applicative
superclass.)
Exercise 18: Repeat Exercise 17 for covariant Day
convolution, given by the tensor
data Day f g a = forall b c. Day (f b) (g c) (b -> c -> a)
from Data.Functor.Day
in package kan-extensions
.
instance Functor2 (Day x) where
Day x f bca) = Day x (fg f) bca
fmap2 fg (
instance (forall x. Functor2 (Day x)) => Bifunctor2 Day where
Day p r bca) = Day (pq p) (rs r) bca
bimap2 pq rs (
assoc :: Day f (Day g h) a -> Day (Day f g) h a
Day f (Day g h dec) bca) = Day (Day f g (,)) h $
assoc (-> bca b (dec d e)
\(b, d) e
unassoc :: Day (Day f g) h a -> Day f (Day g h) a
Day (Day f g bce) h eda) = Day f (Day g h (,)) $
unassoc (-> eda (bce b c) d
\b (c, d)
left :: f a -> Day Identity f a
= Day (Identity ()) f (flip const)
left f
unleft :: Functor f => Day Identity f a -> f a
Day b f bca) = bca (runIdentity b) <$> f
unleft (
right :: f a -> Day f Identity a
= Day f (Identity ()) const
right f
unright :: Functor f => Day f Identity a -> f a
Day f c bca) = flip bca (runIdentity c) <$> f
unright (
class Functor m => MonoidObject (m :: Type -> Type) where
mu :: Day m m a -> m a
eta :: Identity a -> m a
To turn Day mb mc f
into an m a
, we need to
apply f
across mb
and mc
:
Day mb mc f) = f <$> mb <*> mc mu (
mu
is liftA2
ing f
, and
applicative Functors are monoid objects in the monoidal category (HaskHask,
Day
, Identity
). eta
is
pure
, like it was for Monads.
What’s the point of working through all these definitions? Even though I said “you do not need to read this”, I think there’s still a payoff. What we have here is a method for generating abstractions: start with a monoidal category that’s related to Hask in some way, turn the handle, and a typeclass comes out. If the typeclass has interesting instances, rewrite it into an ergonomic interface.
We can also start reversing arrows and seeing what else falls out.
There is a contravariant
form of Day convolution and if you follow that line of thought far
enough, you get contravariant forms
of Applicative
and Alternative
. I once
tried abstracting
over the covariant and contravariant versions of these classes to
make an abstraction unifying parsers and pretty-printers, but did not
get far. Ed Kmett used Divisible
(contravariant Applicative
) and Decidable
(contravariant Alternative
) to build discrimination
,
a library of fast
generic sorting/joining functions.
We can also look for the same patterns in different categories.
Benjamin Pizza Hodgson has a great article about functors
from (k -> Type)
to Type
, describing a
pattern that appears in the hkd
,
rank2classes
,
Conkin
,
and barbies
packages.
Sometimes there is no payoff, or the payoff is not immediately
obvious. We found no interesting monoid objects in (Hask, Either
,
Void
), and trying to write out a class for comonoids
doesn’t look fruitful, because we can trivially write an instance for
any type:
class Comonoid m where
comempty :: m -> ()
comappend :: m -> (m, m)
instance Comonoid a where
= ()
comempty _ = (m, m) comappend m
But comonoids suddenly become a lot more interesting when you have linear
arrows — class Dupable
is the typeclass for comonoids in linear Haskell.
And all that makes me think the meme words have some use after all, but not as a way to understand deep secrets of the Haskell universe. I think instead that they are one way to learn one tool in one part of the category-theoretic toolbox.
E. Rivas and M. Jaskelioff, “Notions of Computation as Monoids”