The short answer: yes, there are 'smaller' categories in Haskell, and you can define functors (not just endofunctors) between them. Whether they are useful is another question.
This is something that I've been wondering about for years. The present question prompted me to take a stab at this. I'm currently making my way through Bartosz Milewski's Category Theory for Programmers for the third time. I'm not sure I got the following right, so I'd appreciate feedback.
Hask
If I understand it correctly, Hask is essentially the category of types (~ category of sets) with bottom (⊥) thrown in to represent non-terminating computation. Here's an attempt at illustrating it:

Each object in Hask is a type like Int
, Bool
, String
, or your own custom types like Reservation
, Order
, etc. A type can be viewed as a set; e.g. Bool
is the set containing True
and False
, String
is the set of all strings, etc. Clearly, many of those sets (like String
) are infinite.
In addition, there's also the special bottom object.
You can map types to other types, but you can't map to something outside of Hask because Hask encompasses all types and expressions:

Here I've illustrated mappings from Hask to Hask by duplicating Hask, but really, the two categories are just two identical images.
A functor is a mapping that not only maps objects, but also morphisms between objects. Much has already been said about this, so the only point I'll make here is that since functors between Hask and Hask don't leave the category, they're functors within Hask, and thus endofunctors. That's the Functor
type class in Haskell.
Unit category
The question, then, is: are there 'smaller' categories within Hask?
As far as I can tell: yes, infinitely many.
One of the simplest categories that exist is a category with a single object and no other morphisms than the identity morphism:

In Haskell, this could be a picture of the unit (()
) type. While ()
is part of Hask, you can also view it as a category in itself. Let's call it Unit.
Free categories
The above Unit category is just an example of a free category. A free category is a category constructed from a directed graph. Here's another graph:

This one has two vertices and two edges. We can construct a category from this graph by interpreting the vertices as objects and the edges as morphisms. We also have to add identity morphisms for each object, as well as composition of morphisms.
In programming, a set with two objects is equivalent to a type with only two inhabitants. You can give these values various names, but such a type is always isomorphic to Bool
.
Functor
Can we define a mapping between the above two categories?
Yes, we can do this by embedding Unit in the 'larger' category. We do that by just arbitrarily pick one of the objects:

Another functor exists that picks the other object.
This is clearly a mapping between categories, so isn't an endofunctor. Is it a proper functor, though?
In order to be a functor, the mapping must not only map objects to objects, but also morphisms to morphisms. This is also the case here, because Unit only has the identity morphism. Thus, we also map the identity morphism to the identity morphism on the target object we've picked. The only compositions possible in Unit is id ∘ id
, id ∘ id ∘ id
, and so on. These all map to id ∘ id
, id ∘ id ∘ id
, etc. on the target object.
I've only been dabbling with category theory for a few years, but I think that this is a proper functor.
The Haskell Category type class
Haskell defines a type class called Category. It doesn't quite fit the above Unit category, or the above free category example, because it assumes that Category
is a higher-kinded type (i.e. that it involves types) in Hask. Still, let's see if we can shoehorn Unit and the above free category into Category
, as well as make a functor out of it.
Unit as Category
Instances of Category
must be higher-kinded types (i.e. cat a b
), so we can't just turn ()
into a Category
instance. We can, however, define a higher-kinded type isomorphic to it:
data U a b = U deriving (Eq, Show)
Like the Const functor, this type defines type variables that it then ignores. Just like ()
, the U
type has only one value, also called U
. (Exercise: show that U
and ()
are isomorphic.)
We can make U
a Category
instance:
instance Category U where
id = U
U . U = U
Is it a proper category, though? Does it obey the laws?
We can use equational reasoning to prove that it does:
Right identity
U . id
= { definition of (.) }
U
Left identity
id . U
= { definition of (.) }
U
Associativity
U . (U . U)
= { definition of (.) }
U . U
= { redundant brackets }
(U . U)
= { definition of (.) }
(U . U) . U
That looks good to me.
The free category example as Category
How about the above example of a free category? Like the above U
type, this tiny category can't be parametrically polymorphic, but again we can define a phantom type:
data Bendo a b = Bendo { runB :: Bool -> Bool }
other :: Bendo a b
other = Bendo not
I've called the type Bendo
for Boolean endomorphism, because that's what it turns out to be. The edges between the two objects (True
and False
) corresponds to picking the other object, which is equivalent to the the built-in not
function.
To model the category in question, the only morphisms allowed are other
and id
, so other functions Bool -> Bool
(like \_ -> True
) should be disallowed. Thus, a module defining Bendo
shouldn't export the data constructor.
Can we make Bendo
a Category
instance?
instance Category Bendo where
id = Bendo id
(Bendo f) . (Bendo g) = Bendo (f . g)
Indeed, this is possible. I'm not going to prove that this is a category, because it's really just the ->
category instance specialised to (->) Bool Bool
.
Functor
Let's now define a functor between U
and Bendo
. To do that, we can use the more general definition of Functor
given in Control.Categorical.Functor. To make all this work, then, I've had to hide the usual definitions given in Prelude
:
import Control.Category
import Control.Categorical.Functor
import Prelude hiding (id, (.), Functor(..))
We're also going to need to support MultiParamTypeClasses
:
{-#LANGUAGE MultiParamTypeClasses #-}
In order to implement that more general Functor
type class, we need a higher-kinded type. Again, let's produce another phantom type for the purpose:
data Embed a = Embed deriving (Eq, Show)
This is enough to define the instance:
instance Functor Embed U Bendo where
fmap U = Bendo id
This maps U
to the identity morhism in Bendo
.
It's a bit awkward to use, but it's possible:
> (runB $ (fmap U :: Bendo (Embed a) (Embed b))) False
False
> (runB $ (fmap U :: Bendo (Embed a) (Embed b))) True
True
Haskell can't figure out what the type of fmap U
is going to be, so you have to tell it. Once you tell it that the result should have the type Bendo (Embed a) (Embed b)
, fmap
maps U
to the identity morphism, which you can then verify by apply runB
on either True
or False
.
Conclusion
Do functors (not just endofunctors) exist in programming? Yes, they do.
Are they useful? It seems to me that if you squint a little, those functors are just a subset of the 'normal' functions. A simplified version of the above functor is just:
uToBendo :: () -> Bool -> Bool
uToBendo () = id
This is just a normal function.
I have to think more about whether there's a more useful application when viewed like this.