[Haskell-cafe] Working inside the fold

Greg Buchholz haskell at sleepingsquirrel.org
Thu Oct 6 14:31:04 EDT 2005



    Recently I've been browsing some of Oleg Kiselyov's articles entitled
"Towards the best collection traversal interface"...

    http://okmij.org/ftp/Computation/Continuations.html#enumerator-stream
    
    A programming language system gives us typically one of the two
    interfaces to systematically access elements of a collection. One
    traversal API is based on enumerators -- e.g., for-each, map, filter
    higher-order procedures -- of which the most general is fold. The 
    second approach relies on streams, a.k.a. cursors, lazy lists. 

...where he argues that (since they're both intraconvertible) a default
enumerator/fold choice is better than the lazy-list approach.  I was
sufficiently intrigued I thought I'd take up the challenge and see what
could be done working inside the fold.  This message is literate Haskell
source, for those of you playing at home.  The first thing to do is
define a few folds which will take the place of lists.  I'll start out
with a finite and infinite one...

>numsTo10 f unit = foldr f unit [1..10]
>nats     f unit = foldr f unit [1..]

If you want the sum of the first ten naturals you'd invoke it as...

*Main> numsTo10 (+) 0
55

...and to see that you can convert back to a list...

*Main> numsTo10 (:) []
[1,2,3,4,5,6,7,8,9,10]

That's nice, but the first thing you'll notice is that while there are
numerous list processing functions in the prelude, there are none for
specifically working inside a fold.  Let's try and define a few...

>map_ :: (a -> b) -> (b -> c -> d) -> a -> c -> d
>map_ f g a b = g (f a) b

...so if we want the sum of the first ten squares...

*Main> numsTo10 (map_ (^2) (+)) 0 
385

...or the actual list...

*Main> numsTo10 (map_ (^2) (:)) []
[1,4,9,16,25,36,49,64,81,100]

...Filter is also a nice function...

>filter_ p f a b = if p a then f a b  else b

*Main> numsTo10 (filter_ odd (:)) []
[1,3,5,7,9]

...and we can also play nice with infinity...

>takeWhile_ unit p f a b = if p a
>                          then f a b
>                          else unit

*Main> nats (takeWhile_ [] (<15) (:)) []
[1,2,3,4,5,6,7,8,9,10,11,12,13,14]

...That's a little bit ugly because you have to supply the unit value
(in this case "[]") for the fold to takeWhile_.  The dropWhile_ function
is also a little quirky, since it uses the tupling trick from...

    "A Tutorial on the Universality and Expressiveness of Fold"
     http://citeseer.ist.psu.edu/hutton93tutorial.html

>dropWhile_ p f a (ys, xs) =((if p a 
>                             then ys 
>                             else f a xs), f a xs)

*Main> numsTo10 (dropWhile_ (<5) (:)) ([],[])
([5,6,7,8,9,10],[1,2,3,4,5,6,7,8,9,10])
*Main> numsTo10 (dropWhile_ (<5) (+)) (0,0)
(45,55)

...where the first member of the pair is the desired answer.  If you
want to do more than one thing inside the fold, "fork" might be the
solution (is there a better name?) 

>fork f g z (x,y) = (f z x, g z y)

*Main> numsTo10 (fork (:) (+)) ([],0)
([1,2,3,4,5,6,7,8,9,10],55)
*Main> numsTo10 (fork (filter_ odd (:)) (fork (+) (*))) ([],(0,1))
([1,3,5,7,9],(55,3628800))

...And you can mostly compose these operations, although for infinite
lists you'll hit bottom if anything other than takeWhile_ is the first
function...

>c = nats (takeWhile_ ([],(0,1)) (<20) 
>            (filter_ even (map_ (^2) (fork (:) (fork (+) (*))))))
>         ([],(0,1))

*Main> c
([4,16,36,64,100,144,196,256,324],(1140,34519618525593600))

...So a few generic munging functions can be defined for inside the fold.
I couldn't think of how to define "take" or "drop" or figure out what a
zipWith would mean.  Are there any other interesting functions that
could be defined?  Is there a better way define these functions?  Is
there anything other than curiosity which would motivate someone to use
these functions?


FWIW,

Greg Buchholz



More information about the Haskell-Cafe mailing list