[Haskell-beginners] Re: proper way to read fold types

dan portin danportin at gmail.com
Mon Jul 26 07:30:16 EDT 2010


I'm still a Haskell newbie, so take this with a grain of salt: the type
signature of *foldr* and *foldr1* confuses me also. While I understand how
each operates, I've never found a description of the type signatures of
either functions which explains why the function argument of *foldr1* is of
type (a -> a -> a) instead of (a -> b -> b). This is the conclusion I came
to. Hopefully it helps; if it's wrong, then hopefully it can be corrected.

Suppose we have a list M = [x1, x2, ..., x(n-1), xn], and we evaluate the
function:

foldr1 *f* M = *f* x1 (*f* x2 ... (*f* x(n-1) xn) ...)

We know that for all xi <- M, xi has type *a*. Suppose that the
function *f*has type (
*a* -> *b* -> *c*) and consider the expression *f* x(i-1) xi, where x(i-1),
xi <- M. Since x(i-1) and xi have type *a*, the expression is well-typed
only if the type *b* is the same as *a*. Because each such expression
resulting from folding *f* into M becomes the second argument to *f*, the
result of evaluating *f* must be a value of type *a*. That is, *c* must be
the same type as *a*.

With *foldr*, however, this isn't necessarily the case. Suppose we have a
list N = [x1, x2, ..., xn], and we evaluate the function:

foldr *f* **v N = *f* x1 (*f* x2 ... (*f* xn v) ...)

There is no reason that *v* must have the same type as each xi <- N, since *
v* is not derived from N. You can see that as *foldr* is evaluated, starting
from the most nested *f*, the value bound to the second argument of each
occurrence of *f* has the same type as the value which is the result of
evaluating *f*. If this is the case, however, then the type of the value
which results from evaluating *foldr*, where *v* has type *b*, must be a
value of type *b*.

You might, however, define a function using *foldr* and *foldr1* which
produce the same result. For instance,

mySum list = foldr (+) 0 list
mySum' list = foldr1 (+) list

In this case, (+) :: (a -> a -> a). So *b* is the same type as *a* and all
is well.




On Mon, Jul 26, 2010 at 12:30 AM, Ertugrul Soeylemez <es at ertes.de> wrote:

> prad <prad at towardsfreedom.com> wrote:
>
> > i'm trying to make sense of the a vs b in foldr, so here goes:
> >
> > foldr takes 3 arguments:
> >       1. some function f, illustrated within () of type b
> >       2. some value of type b
> >       3. some list with elements of type a
> >
> > foldr applies f to each element of [a], computing a new function (f a)
> > which is then applied to the item of type b, computing a result of
> > type b, which is then combined with #2 (this would be the accumulator)
> >
> > finally, the net computation of foldr results in some item of type b.
>
> You think too complicated.  It's really very simple.  Look at how foldr
> is defined:
>
>  foldr f z []     = z
>  foldr f z (x:xs) = x `f` foldr f z xs
>
> In the recursive case the folding function gets its two arguments:  The
> first argument is the head element of the list.  The second argument is
> the result of folding the rest of the list.  You can read from this
> function immediately that it really replaces each (:) by 'f' and the []
> by 'z' in a right-associative manner.
>
>  foldr (+) 0 [a,b,c] = a + (b + (c + 0))
>
>
> > foldr1 takes 2 arguments:
> >       1. some function g, illustrated within () of type a
> >       2. some list with elements of type a
> >
> > foldr1 applies g to each element of [a], computing a new function (g
> > a) which is then applied to a non-explicitly defined item of type a,
> > computing a result also of type a.
> >
> > the net computation of foldr1 results in some item of type a.
>
> Simple:
>
>  foldr1 f [x]    = x
>  foldr1 f (x:xs) = x `f` foldr1 f xs
>
> This is just a simplified version of foldr.  The base element is passed
> explicitly in foldr as 'z'.  Here the base element is just the last
> element of the list to be folded.  For some folds, having an extra base
> element wouldn't make much sense, for example for the 'maximum'
> function:
>
>  myMaximum = foldr1 max
>
> This is why there is the foldr1 variant of foldr.  But of course, you
> would write 'maximum' as a left fold (foldl1), not a right fold.
>
>  foldr1 max [a,b,c] = a `max` (b `max` c)
>
>
> > i know how i can use the folds in some situations, but explaining
> > their type definitions to reveal how they work, is coming out pretty
> > convoluted when i make the attempt. :(
>
> Just read the type of the function and its definition.  For most
> functions in Haskell, you will even find that reading the type signature
> and the name of the function suffices to understand, what it does.
> Trying to interpret combinators (or even to find metaphors, as many
> people do) is not always the right thing to do.
>
> However, in this case there is an easy interpretation:  It takes the
> list elements and puts a binary operator between each of them.  It also
> appends a base element (usually some kind of neutral element or initial
> value) to the list, so that the empty list is allowed.  That's it.
>
>
> Greets,
> Ertugrul
>
>
> --
> nightmare = unsafePerformIO (getWrongWife >>= sex)
> http://ertes.de/
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20100726/11afba04/attachment-0001.html


More information about the Beginners mailing list