Summary: (>>=)
and traverse
look similar because they both are arrow mappings of functors, while foldMap
is (almost) a specialised traverse
.
Before we begin, there is one bit of terminology to explain. Consider fmap
:
fmap :: Functor f => (a -> b) -> (f a -> f b)
A Haskell Functor
is a functor from the Hask category (the category with Haskell functions as arrows) to itself. In category theory terms, we say that the (specialised) fmap
is the arrow mapping of this functor, as it is the part of the functor that takes arrows to arrows. (For the sake of completeness: a functor consists of an arrow mapping plus an object mapping. In this case, the objects are Haskell types, and so the object mapping takes types to types -- more specifically, the object mapping of a Functor
is its type constructor.)
We will also want to keep in mind the category and functor laws:
-- Category laws for Hask:
f . id = id
id . f = f
h . (g . f) = (h . g) . f
-- Functor laws for a Haskell Functor:
fmap id = id
fmap (g . f) = fmap g . fmap f
In what follows, we will work with categories other than Hask, and functors which are not Functor
s. In such cases, we will replace id
and (.)
by the appropriate identity and composition, fmap
by the appropriate arrow mapping and, in one case, =
by an appropriate equality of arrows.
(=<<)
To begin with the more familiar part of the answer, for a given monad m
the a -> m b
functions (also known as Kleisli arrows) form a category (the Kleisli category of m
), with return
as identity and (<=<)
as composition. The three category laws, in this case, are just the monad laws:
f <=< return = f
return <=< f = f
h <=< (g <=< f) = (h <=< g) <=< f
Now, your asked about flipped bind:
(=<<) :: Monad m => (a -> m b) -> (m a -> m b)
It turns out that (=<<)
is the arrow mapping of a functor from the Kleisli category of m
to Hask. The functor laws applied to (=<<)
amount to two of the monad laws:
return =<< x = x -- right unit
(g <=< f) =<< x = g =<< (f =<< x) -- associativity
traverse
Next, we need a detour through Traversable
(a sketch of a proof of the results in this section is provided at the end of the answer). First, we note that the a -> f b
functions for all applicative functors f
taken at once (as opposed to one at each time, as when specifying a Kleisli category) form a category, with Identity
as identity and Compose . fmap g . f
as composition. For that to work, we also have to adopt a more relaxed equality of arrows, which ignores the Identity
and Compose
boilerplate (which is only necessary because I am writing this in pseudo-Haskell, as opposed to proper mathematical notation). More precisely, we will consider that that any two functions that can be interconverted using any composition of the Identity
and Compose
isomorphisms as equal arrows (or, in other words, we will not distinguish between a
and Identity a
, nor between f (g a)
and Compose f g a
).
Let's call that category the "traversable category" (as I cannot think of a better name right now). In concrete Haskell terms, an arrow in this category is a function which adds an extra layer of Applicative
context "below" any previous existing layers. Now, consider traverse
:
traverse :: (Traversable t, Applicative f) => (a -> f b) -> (t a -> f (t b))
Given a choice of traversable container, traverse
is the arrow mapping of a functor from the "traversable category" to itself. The functor laws for it amount to the traversable laws.
In short, both (=<<)
and traverse
are analogues of fmap
for functors involving categories other than Hask, and so it is not surprising that their types are a bit similar to each other.
foldMap
We still have to explain what all of that has to do with foldMap
. The answer is that foldMap
can be recovered from traverse
(cf. danidiaz's answer -- it uses traverse_
, but as the applicative functor is Const m
the result is essentially the same):
-- cf. Data.Traversable
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> (t a -> m)
foldMapDefault f = getConst . traverse (Const . f)
Thanks to the const
/getConst
isomorphism, this is clearly equivalent to:
foldMapDefault' :: (Traversable t, Monoid m)
=> (a -> Const m b) -> (t a -> Const m (t b))
foldMapDefault' f = traverse f
Which is just traverse
specialised to the Monoid m => Const m
applicative functors. Even though Traversable
is not Foldable
and foldMapDefault
is not foldMap
, this provides a decent justification for why the type of foldMap
resembles that of traverse
and, transitively, that of (=<<)
.
As a final observation, note that the arrows of the "traversable category" with applicative functor Const m
for some Monoid
m
do not form a subcategory, as there is no identity unless Identity
is among the possible choices of applicative functor. That probably means there is nothing else of interest to say about foldMap
from the perspective of this answer. The only single choice of applicative functor that gives a subcategory is Identity
, which is not at all surprising, given how a traversal with Identity
amounts to fmap
on the container.
Appendix
Here is a rough sketch of the derivation of the traverse
result, yanked from my notes from several months ago with minimal editing. ~
means "equal up to (some relevant) isomorphism".
-- Identity and composition for the "traversable category".
idT = Identity
g .*. f = Compose . fmap g . f
-- Category laws: right identity
f .*. idT ~ f
f .*. idT
Compose . fmap f . idT
Compose . fmap f . Identity
Compose . Identity . f
f -- using getIdentity . getCompose
-- Category laws: left identity
idT .*. f ~ f
idT .*. f
Compose . fmap Identity . f
f -- using fmap getIdentity . getCompose
-- Category laws: associativity
h .*. (g .*. f) ~ (h .*. g) .*. f
h .*. (g .*. f) -- LHS
h .*. (Compose . fmap g . f)
Compose . fmap h . (Compose . fmap g . f)
Compose . Compose . fmap (fmap h) . fmap g . f
(h .*. g) .*. f -- RHS
(Compose . fmap h . g) .*. f
Compose . fmap (Compose . fmap h . g) . f
Compose . fmap (Compose . fmap h) . fmap g . f
Compose . fmap Compose . fmap (fmap h) . fmap g . f
-- using Compose . Compose . fmap getCompose . getCompose
Compose . Compose . fmap (fmap h) . fmap g . f -- RHS ~ LHS
-- Functor laws for traverse: identity
traverse idT ~ idT
traverse Identity ~ Identity -- i.e. the identity law of Traversable
-- Functor laws for traverse: composition
traverse (g .*. f) ~ traverse g .*. traverse f
traverse (Compose . fmap g . f) ~ Compose . fmap (traverse g) . traverse f
-- i.e. the composition law of Traversable
concatMap'
isfoldMap
from theFoldable
class inData.Foldable
. – Cassy