Foldable, Monoid and Monad

此生再无相见时 提交于 2019-11-28 20:05:06

问题


Consider the following signature of foldMap

foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m

This is very similar to "bind", just with the arguments swapped:

(>>=) :: Monad m => m a -> (a -> m b) -> m b

It seems to me that there therefore must be some sort of relationship between Foldable, Monoid and Monad, but I can't find it in the superclasses. Presumably I can transform one or two of these into the other but I'm not sure how.

Could that relationship be detailed?


回答1:


Monoid and Monad

Wow, this is actually one of the rare times we can use the quote:

A monad is just a monoid in the category of endofunctors, [...]

Let's start with a monoid. A monoid in the category Set of sets is a set of elements m with an empty element mempty and an associative function mappend to combine elements such that

mempty `mappend` x == x -- for any x
x `mappend` mempty == x -- for any x
-- and
a `mappend` (b `mappend` c) == (a `mappend` b) `mappend` c -- for all a, b, c

Note that a monoid is not limited to sets, there also exist monoids in the category Cat of categories (monads) and so on. Basically anytime you have an associative binary operation and an identity for it.

Now a monad, which is a "monoid in the category of endofunctors" has following properties:

It's an endofunctor, that means it has type * -> * in the Category Hask of Haskell types.

Now, to go further you must know a little bit of category theory I will try to explain here: Given two functors F and G, there exists a natural transformation from F to G iff there exists a function α such that every F a can be mapped to a G a. α can be many-to-one, but it has to map every element of F a. Roughly said, a natural transformation is a function between functors.

Now in category theory, there can be many functors between two categories. Ina simplified view it can be said that we don't even care about which functors map from where to where, we only care about the natural transformations between them.

Coming back to monad, we can now see that a "monoid in the category of endofunctors" must posess two natural transformations. Let's call our monad endofunctor M:

A natural transformation from the identity (endo)functor to the monad:

η :: 1 -> M -- this is return

And a natural transformation from the conposition of two monads and produce a third one:

μ :: M × M -> M

Since × is the composition of functors, we can (roughly speaking) also write:

μ :: m a × m a -> m a
μ :: (m × m) a -> m a
μ :: m (m a) -> m a -- join in Haskell

Satisfying these laws:

μ . M μ == μ . μ M
μ . M η == μ . η M

So, a monad is a special case of a monoid in the category of endofunctors. You can't write a monoid instance for monad in normal Haskell, since Haskell's notion of composition is too weak (I think; This is because functions are restricted to Hask and it's weaker than Cat). See this for more information.

What about Foldable?

Now as for Foldable: there exist definitions of folds using a custom binary function to combine the elements. Now you could of course supply any function to combine elements, or you could use an existing concept of combining elements, the monoid. Again, please note that this monoid restricted to the set monoid, not the catorical definition of monoid.

Since the monoid's mappend is associative, foldl and foldr yield the same result, which is why the folding of monoids can be reduced to fold :: Monoid m, Foldable t => t m -> m. This is an obvious connection between monoid and foldable.

@danidiaz already pointed out the connection between Applicative, Monoid and Foldable using the Const functor Const a b = Const a, whose applicative instance requires the first parameter of Const to be a monoid (no pure without mempty (disregarding undefined)).

Comparing monad and foldable is a bit of a stretch in my opinion, since monad is more powerful than foldable in the sense that foldable can only accumulate a list's values according to a mapping function, but the monad bind can structurally alter the context (a -> m b).




回答2:


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 Functors. 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 = return
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



回答3:


When a container is Foldable, there is a relationship between foldMap and Applicative (which is a superclass of Monad).

Foldable has a function called traverse_, with signature:

traverse_ :: Applicative f => (a -> f b) -> t a -> f ()

One possible Applicative is Constant. To be an Applicative, it requires the "accumulator" parameter to be a Monoid:

newtype Constant a b = Constant { getConstant :: a } -- no b value at the term level!

Monoid a => Applicative (Constant a)

for example:

gchi> Constant (Sum 1) <*> Constant (Sum 2) :: Constant (Sum Int) whatever
Constant (Sum {getSum = 3})

We can define foldMap in terms of traverse_ and Constant this way:

foldMap' :: (Monoid m, Foldable t) => (a -> m) -> t a -> m
foldMap' f = getConstant . traverse_ (Constant . f)

We use traverse_ to go through the container, accumulating values with Constant, and then we use getConstant to get rid of the newtype.



来源:https://stackoverflow.com/questions/39951758/foldable-monoid-and-monad

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!