[Haskell-beginners] Data.Foldable/foldMap question

Daniel Fischer daniel.is.fischer at googlemail.com
Sat May 28 23:10:17 CEST 2011


On Saturday 28 May 2011 22:37:45, Patrick LeBoutillier wrote:
> Hi,
> 
> I'm reading the LYAH book and on page 263 it says that if you define
> Data.Foldable.foldMap you get Data.Foldable.foldl and
> Data.Foldable.foldl for "free". The default implementation code of
> Data.Foldable.foldr is:
> 
>         foldr :: (a -> b -> b) -> b -> t a -> b
>         foldr f z t = appEndo (foldMap (Endo . f) t) z
> 
> I don't understand this code, but more specifically I don't get how
> there can a Monoid constraint on foldMap's return type and not on
> foldr/foldl.
> 
> Can any one explain what Endo is and how it works?

newtype Endo a = Endo { appEndo :: a -> a }

So an (Endo a) is a wrapped function (a -> a), an endomorphism of a (in the 
category Hask; ignore this if you don't know what that means).

The type of f in foldr is

f :: a -> b -> b = a -> (b -> b),

hence (f x) :: (b -> b) and

Endo . f :: a -> Endo b

and there is a Monoid instance for (Endo b)
(mempty is (Endo id), (Endo g) `mappend` (Endo h) = Endo (g . h)), so
(Endo . f) is a suitable argument for foldMap.

foldMap (Endo . f) t builds an endomorphism of b [wrapped in the newtype], 
which is then unwrapped by appEndo to yield a function (b -> b) which 
finally is applied to the supplied element z of b.

Without the wrapper and for lists:

foldr f z [1,2,3]
~> f 1 (foldr f z [2,3])   === (f 1) (foldr f z [2,3])
~> (f 1) ((f 2) (foldr f z [3]))
= ((f 1) . (f 2)) (foldr f z [3])
~> ((f 1) . (f 2)) ((f 3) (foldr f z []))
~> ((f 1) . (f 2) . (f 3)) (foldr f z [])
~> ((f 1) . (f 2) . (f 3)) z

The composition (f 1) . (f 2) . (f 3) is what foldMap builds [modulo the 
wrapper Endo, with the wrapper it is

Endo (f 1) `mappend` Endo (f 2) `mappend` Endo (f 3)
= Endo ((f 1) . (f 2) . (f 3))

which is then unwrapped by appEndo].

> 
> 
> Thanks a lot,
> 
> Patrick



More information about the Beginners mailing list