[Haskell-beginners] understanding curried function calls

John Wiegley johnw at newartisans.com
Wed Aug 20 19:15:49 UTC 2014


>>>>> Dimitri DeFigueiredo <defigueiredo at ucdavis.edu> writes:

> Eventually, I would like to be able to grok famous beasts like this one.

> foldl :: (a -> b -> a) -> a -> [b] -> a
> foldl f a bs =
>    foldr (\b g x -> g (f x b)) id bs a

Let's uncurry every function involved manually, after swapping the type
variables to make what comes later less confusing:

    foldl :: (b -> a -> b) -> b -> [a] -> b
    foldl f b as = foldr (\a g b -> g (f b a)) id as b

    foldl' :: (b -> a -> b) -> b -> ([a] -> b)
    foldl' f b = \as -> foldr (\a g b -> g (f b a)) id as b

    foldl'' :: (b -> a -> b) -> (b -> ([a] -> b))
    foldl'' f = \b -> \as -> foldr (\a g b -> g (f b a)) id as b

    foldl''' :: (b -> (a -> b)) -> (b -> ([a] -> b))
    foldl''' f = \b -> \as -> (((foldr (\a -> \g -> \b -> g ((f b) a))) id) as) b

We have a function that takes a function and returns a function.  The function
it takes maps a value to *a function from an element to a value of the same
type*.  The function it returns maps a value to a function over a list of
elements to a value of the same type.

Or: Given a function a -> (b -> a), foldl lifts this to a function over lists
of elements, a -> ([b] -> a).  Not quite a map, since map lifts a -> b to [a]
-> [b].  But map is just a fold:

    map f :: (a -> b) -> ([a] -> [b])
    map f = foldl (\b -> \a -> b ++ [f a]) []

Looking at the types, we're dropping "b ->" from the input and output
functions of foldl, and changing the final result to a list:

    foldl :: (b -> (a -> b)) -> (b -> ([a] ->  b))
    map   ::       (a -> b)  ->       ([a] -> [b])

Folds expose the "book-keeping" value that map uses to accumulate its result,
allowing us to accumulate any value we want.  Now foldMap should make more
sense (I've specialized it to lists here for the sake of presentation):

    foldMap' :: Monoid b => (a -> b) -> ([a] -> b)

We don't have access to the accumulator, as we do with foldl, but knowing it's
a Monoid we can merge values into the result by returning monoidal values.

All of these types can be generalized to work over any notion of "container"
using Data.Foldable:

    foldl   :: Foldable f           => (b -> (a -> b)) -> (b -> (f a -> b))
    fmap    :: Functor f            => (a -> b) -> (f a -> f b)
    foldMap :: Foldable f, Monoid b => (a -> b) -> (f a -> b)

I have diverted from the main theme of how to read curried function types, but
I wanted to drive home how potent this notion of "functions returning
functions" is, and that currying really only gives us a more convenient way of
naming the arguments to the lambda abstractions being returned.  (In GHC there
can also be performance differences between the two, but otherwise they should
be regarded as equivalent).

John


More information about the Beginners mailing list