Why is it sometimes possible to fold an infinite list from the right? - haskell

I have been going through the excellent CIS 194 course when I got stuck on Part 5 of Homework 6. It revolves around implementing the ruler function without any divisibility testing.
I found that it is possible to build the ruler function by continuously interspersing an accumulator with values from an infinite list.
nats = [0,1,2,3,..]
[3]
[2,3,2]
[1,2,1,3,1,2,1]
[0,1,0,2,0,1,0,3,0,1,0,2,0]
Then I tried implementing this algorithm for Stream datatype which is a list without nil
data Stream a = Cons a (Stream a)
streamToList :: Stream a -> [a]
streamToList (Cons x xs) = x : streamToList xs
instance Show a => Show (Stream a) where
show = show . take 20 . streamToList
streamFromSeed :: (a -> a) -> a -> Stream a
streamFromSeed f x = Cons x (streamFromSeed f (f x))
nats :: Stream Integer
nats = streamFromSeed succ 0
interleave x (Cons y ys) = Cons x (Cons y (interleave x ys))
foldStream f (Cons x xs) = f x (foldStream f xs)
ruler = foldStream interleave nats
As expected, I got stackoverflow error since I was trying to fold from the right. However, I was surprised to see the same algorithm work for normal infinite lists.
import Data.List
interleave x list = [x] ++ (intersperse x list) ++ [x]
ruler = take 20 (foldr interleave [] [0..])
What am I missing? Why one implementation works while the other doesn't?

Your interleave is insufficiently lazy. The magic thing that right folds must do to work on infinite structures is to not inspect the result of the folded value too closely before they do the first bit of computation. So:
interleave x stream = Cons x $ case stream of
Cons y ys -> Cons y (interleave x ys)
This produces Cons x _ before inspecting stream; in contrast, your version requires stream to be evaluated a bit before it can pass to the right hand side of the equation, which essentially forces the entire fold to happen before any constructor gets produced.
You can also see this in your list version of interleave:
interleave x list = [x] ++ intersperse x list ++ [x]
The first element of the returned list (x) is known before intersperse starts pattern matching on list.

We can inspect the source code of foldr [src]. A less noisy version looks like:
foldr f z [] = z
foldr f z (x:xs) = f x (foldr f z xs)
Haskell does not evaluate eagerly. This thus means that, unless you need (foldr f z xs), it will not evaluate the accumulator. This thus means that f does not need the second parameter, for example because the first item x has a certain value, it will not evaluate the accumulator.
For example if we implement takeWhileNeq:
takeWhileNeq a = foldr f []
where f x xs -> if x == a then [] else (x:xs)
if we thus run this on a list takeWhileNeq 2 [1,4,2,5], then it will not evaluate anything. If we however want to print the result it will evaluate this as:
f 1 (foldr f [4,2,5])
and f will inspect if 1 == 2, since that is not the case, it will return (x:xs), so:
-> 1 : foldr f [4,2,5]
so now it will evaluate 4 == 2, and because this is false, it will evaluate this to:
-> 1 : (4 : foldr f [2,5])
now we evaluate 2 == 2, and since this is True, the function returns the empty list, and ingores the accumulator, so it will never look at foldr f [5]:
-> 1 : (4 : [])
For an infinite list, it will thus also result an empty list and ignore folding the rest of the list.

Related

How to apply a function to a specific element of a list

How can I apply a function to only a single element of a list?
Any suggestion?
Example:
let list = [1,2,3,4,3,6]
function x = x * 2
in ...
I want to apply function only to the first occurance of 3 and stop there.
Output:
List = [1,2,6,4,3,6] -- [1, 2, function 3, 4, 3, 6]
To map or not to map, that is the question.
Better not to map.
Why? Because map id == id anyway, and you only want to map through one element, the first one found to be equal to the argument given.
Thus, split the list in two, change the found element, and glue them all back together. Simple.
See: span :: (a -> Bool) -> [a] -> ([a], [a]).
Write: revappend (xs :: [a]) (ys :: [a]) == append (reverse xs) ys, only efficient.
Or fuse all the pieces together into one function. You can code it directly with manual recursion, or using foldr. Remember,
map f xs = foldr (\x r -> f x : r) [] xs
takeWhile p xs = foldr (\x r -> if p x then x : r else []) [] xs
takeUntil p xs = foldr (\x r -> if p x then [x] else x : r) [] xs
filter p xs = foldr (\x r -> if p x then x : r else r) [] xs
duplicate xs = foldr (\x r -> x : x : r) [] xs
mapFirstThat p f xs = -- ... your function
etc. Although, foldr won't be a direct fit, as you need the combining function of the (\x xs r -> ...) variety. That is known as paramorphism, and can be faked by feeding tails xs to the foldr, instead.
you need to maintain some type of state to indicate the first instance of the value, since map will apply the function to all values.
Perhaps something like this
map (\(b,x) -> if (b) then f x else x) $ markFirst 3 [1,2,3,4,3,6]
and
markFirst :: a -> [a] -> [(Boolean,a)]
markFirst a [] = []
markFirst a (x:xs) | x==a = (True,x): zip (repeat False) xs
| otherwise = (False,x): markFirst a xs
I'm sure there is an easier way, but that's the best I came up with at this time on the day before Thanksgiving.
Here is another approach based on the comment below
> let leftap f (x,y) = f x ++ y
leftap (map (\x -> if(x==3) then f x else x)) $ splitAt 3 [1,2,3,4,3,6]
You can just create a simple function which multiples a number by two:
times_two :: (Num a) => a -> a
times_two x = x * 2
Then simply search for the specified element in the list, and apply times_two to it. Something like this could work:
map_one_element :: (Eq a, Num a) => a -> (a -> a) -> [a] -> [a]
-- base case
map_one_element _ _ [] = []
-- recursive case
map_one_element x f (y:ys)
-- ff element is found, apply f to it and add rest of the list normally
| x == y = f y : ys
-- first occurence hasnt been found, keep recursing
| otherwise = y : map_one_element x f ys
Which works as follows:
*Main> map_one_element 3 times_two [1,2,3,4,3,6]
[1,2,6,4,3,6]

Is using fold less efficient than standard recursion

I'm going through the Learn You a Haskell book right now and I'm curious about how this particular example works. The book first demonstrates an implementation of findKey using traditional recursion:
findKey :: (Eq k) => k -> [(k,v)] -> Maybe v
findKey key [] = Nothing
findKey key ((k,v):xs) = if key == k
then Just v
else findKey key xs
The book then follows up with a shorter implementation using foldr
findKey :: (Eq k) => k -> [(k,v)] -> Maybe v
findKey key = foldr (\(k,v) acc -> if key == k then Just v else acc) Nothing
With the standard recursion, the function should immediately return once it hits the first element with the provided key. If I understand the foldr implementation correctly, it will iterate over the entire list every time, even if it matched the first element it came across. That doesn't seem like a very efficient way to handle the problem.
Is there something I'm not getting about how the foldr implementation works? Or is there some kind of magic within Haskell that makes this implementation not quite as inefficient as I think it is?
foldr is written using standard recursion.
The recursive call to foldr is hidden inside of acc. If your code doesn't use acc, it will never be computed (because Haskell is lazy). So the foldr version is efficient and will also return early.
Here's an example demonstrating this:
Prelude> foldr (\x z -> "done") "acc" [0 ..]
"done"
This expression returns "done" immediately, even though the input list is infinitely long.
If foldr is defined as:
foldr f z (x : xs) = f x (foldr f z xs)
foldr _ z [] = z
, then evaluation goes via
f x (foldr f z xs)
where
f = \x z -> "done"
x = 0
z = "acc"
xs = ... -- unevaluated, but is [1 ..]
which is
(\x z -> "done") 0 (foldr (\x z -> "done") "acc" [1 ..])
which turns into "done" because the first function doesn't use z, so the recursive call is never needed.
If I understand the foldr implementation correctly, it will iterate over the entire list every time, even if it matched the first element it came across.
This is wrong. foldr will evaluate the list only as much as needed.
E.g.
foldr (&&) True [True, False, error "unreached code here"]
returns False since the error is never evaluated, precisely as in
(True && (False && (error "unreached code here" && True)))
Indeed, since the end of the list is never reached, we can also write
foldr (&&) (error "end") [True, False, error "unreached code here"]
and still obtain False.
Here is code which demonstrates that foldr does indeed "short-circuit" the evaluation of findKey:
import Debug.Trace
findKey :: (Eq k) => k -> [(k,v)] -> Maybe v
findKey key = foldr (\(k,v) acc -> if key == k then Just v else acc) Nothing
tr x = trace msg x
where msg = "=== at: " ++ show x
thelist = [ tr (1,'a'), tr (2,'b'), tr (3, 'c'), tr (4, 'd') ]
An example of running findKey in ghci:
*Main> findKey 2 thelist
=== at: (1,'a')
=== at: (2,'b')
Just 'b'
*Main>
Think of foldr using the following definition (using standard recursion):
foldr :: (a -> b -> b) -> b -> [a] -> b
foldr f e [] = e
foldr f e (x:xs) = f x (foldr f e xs)
The third line shows that the second implementation for findKey will return upon finding the first match.
As a sidenote: assume you had the following definition (which does not have identical functionality) for findKey (as an exercise you might want to rewrite the definition using foldr):
findKey :: (Eq k) => k -> [(k,v)] -> [v]
findKey key [] = []
findKey key ((kHead, vHead):rest) = if (key == kHead) then vHead:(findKey key rest) else findKey key rest
Now you might think that this would iterate through the whole input list. Depending on how you invoke this function, it could be the case that it iterates through the whole list, but at the same time this can give you the first match efficiently too. Due to Haskell's lazy evaluation the following code:
head (findKey key li)
will give you the first match (assuming that there's one) with the same efficiency as your first example.
foldr f z [a,b,c,...,n] ==
a `f` (b `f` (c `f` (... (n `f` z) ...))) ==
f a (foldr f z [b,c,...,n]) ==
f a acc where acc = foldr f z [b,c,...,n]
So if your f returns before forcing acc, acc remains not forced, i.e. no part of the list argument beyond its head element a is accessed, like e.g. when you have
f a acc = ...
If, on the other hand, your f does force its second argument, e.g. if it's defined as
f a (x:xs) = ...
then the acc is forced before f starts its work, and the list will be accessed in whole before the processing begins -- in whole, because acc = f b acc2 and that invocation of f must force its second argument, acc2, so its value, acc, can be forced (pattern-matched with (x:xs), that is); and so forth.

Haskell - Writing foldr recursively

I am trying to write the library function foldr using recursion. However, I am getting syntax errors and not sure about the functional correctness. This is my code:
foldr :: (a -> b) -> [a] -> [b]
foldr f [] = []
foldr f xs = foldr f (init xs) : f (last xs)
I would appreciate it if I can get some help on this
That is not the type of the foldr function. That is the type of the map function.
But that said, : concatenates one element to the front of a list. The way you are using it attempts to concatenate one element to the end of a list, which does not work.
The closest thing to what you mean -- which is still O(n^2) and deeply inefficient -- is to replace the last line with
foldr f xs = foldr f (init xs) ++ [f (last xs)]

Function using foldr is too eager

I have a little alternative implementation of groupBy, which is more useful to me than the version in Data.List, because it doesn't require the test to be an equivalence relation:
groupBy' :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy' f = foldr step []
where step x [] = [[x]]
step x (xs:xss)
| x `f` head xs = (x:xs):xss
| otherwise = [x]:xs:xss
However, it's too eager and won't start computing for inputs like groupBy' (<) [1,2,3,2,3,4,1,undefined]. I have read the HaskellWiki and Wikibooks articles which explain why certain things, like pattern matches, can make functions less lazy, and I think I understand most of the examples given there. Still, I don't understand why this function can't start producing output until it hits the undefined. Are the pattern matches causing this behavior?
Since I have just read those articles, it's maybe lack of experience that makes me fail to apply what I read there to my example code. So, how could this particular implementation be changed in order to behave more lazily?
The key problem is that you know that step x xss will always produce a result of the form (x:_):_, but you are "hiding" this behind the pattern matches, so Haskell is forced to evaluate those first to determine which case of step to choose before it even sees those constructors.
In general, for foldr f x to be able to produce any output before reaching the end of the list, f must be able to produce some output before examining its second argument.
We can fix this by splitting step into two, so that we can produce the two (:) constructors before doing the pattern matching on the second argument.
groupBy' f = foldr step []
where step x xss = let (ys, yss) = step' x xss in (x:ys):yss
step' x [] = ([], [])
step' x (xs:xss) | f x (head xs) = (xs, xss)
| otherwise = ([], xs:xss)
This is about as lazy as you can get it.
*Main> groupBy' (<) [1, 2, 3, 2, 3, 4, 1, undefined]
[[1,2,3],[2,3,4],[1*** Exception: Prelude.undefined
foldr step [] [1,2,3,...] will expand to step 1 (foldr step [] [2,3]). Now step needs to decide whether to go in its first case or the second. For that it needs to know whether foldr step [] [2,3,...] evaluates to an empty list. For that it needs to know whether step 2 (foldr step [] [3,...]) returns the empty list (which it never will, but Haskell does not know that). This goes on until the end of the list is reached (and if the list doesn't have an end, it goes on forever).
It is difficult for me to understand what your code will do when f is not an equivalence relation, but I guess that you want something like the following code:
groupBy' :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy' f [] = []
groupBy' f [x] = [[x]]
groupBy' f (x : xs)
| x `f` head xs = (x : head l) : tail l
| otherwise = [x] : l
where
l = groupBy' f xs
or equivalently without using head or tail:
groupBy' :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy' f [] = []
groupBy' f (x : xs) = hd : tl
where
(hd, tl) = go x xs
go x [] = ([x], [])
go x xs#(x' : xs')
| x `f` x' = (x : hd', tl')
| otherwise = ([x], hd' : tl')
where
(hd', tl') = go x' xs'

Implement zip using foldr

I'm currently on chapter 4 of Real World Haskell, and I'm trying to wrap my head around implementing foldl in terms of foldr.
(Here's their code:)
myFoldl :: (a -> b -> a) -> a -> [b] -> a
myFoldl f z xs = foldr step id xs z
where step x g a = g (f a x)
I thought I'd try to implement zip using the same technique, but I don't seem to be making any progress. Is it even possible?
zip2 xs ys = foldr step done xs ys
where done ys = []
step x zipsfn [] = []
step x zipsfn (y:ys) = (x, y) : (zipsfn ys)
How this works: (foldr step done xs) returns a function that consumes
ys; so we go down the xs list building up a nested composition of
functions that will each be applied to the corresponding part of ys.
How to come up with it: I started with the general idea (from similar
examples seen before), wrote
zip2 xs ys = foldr step done xs ys
then filled in each of the following lines in turn with what it had to
be to make the types and values come out right. It was easiest to
consider the simplest cases first before the harder ones.
The first line could be written more simply as
zip2 = foldr step done
as mattiast showed.
The answer had already been given here, but not an (illustrative) derivation. So even after all these years, perhaps it's worth adding it.
It is actually quite simple. First,
foldr f z xs
= foldr f z [x1,x2,x3,...,xn] = f x1 (foldr f z [x2,x3,...,xn])
= ... = f x1 (f x2 (f x3 (... (f xn z) ...)))
hence by eta-expansion,
foldr f z xs ys
= foldr f z [x1,x2,x3,...,xn] ys = f x1 (foldr f z [x2,x3,...,xn]) ys
= ... = f x1 (f x2 (f x3 (... (f xn z) ...))) ys
As is apparent here, if f is non-forcing in its 2nd argument, it gets to work first on x1 and ys, f x1r1ys where r1 =(f x2 (f x3 (... (f xn z) ...)))= foldr f z [x2,x3,...,xn].
So, using
f x1 r1 [] = []
f x1 r1 (y1:ys1) = (x1,y1) : r1 ys1
we arrange for passage of information left-to-right along the list, by calling r1 with the rest of the input list ys1, foldr f z [x2,x3,...,xn]ys1 = f x2r2ys1, as the next step. And that's that.
When ys is shorter than xs (or the same length), the [] case for f fires and the processing stops. But if ys is longer than xs then f's [] case won't fire and we'll get to the final f xnz(yn:ysn) application,
f xn z (yn:ysn) = (xn,yn) : z ysn
Since we've reached the end of xs, the zip processing must stop:
z _ = []
And this means the definition z = const [] should be used:
zip xs ys = foldr f (const []) xs ys
where
f x r [] = []
f x r (y:ys) = (x,y) : r ys
From the standpoint of f, r plays the role of a success continuation, which f calls when the processing is to continue, after having emitted the pair (x,y).
So r is "what is done with more ys when there are more xs", and z = const [], the nil-case in foldr, is "what is done with ys when there are no more xs". Or f can stop by itself, returning [] when ys is exhausted.
Notice how ys is used as a kind of accumulating value, which is passed from left to right along the list xs, from one invocation of f to the next ("accumulating" step being, here, stripping a head element from it).
Naturally this corresponds to the left fold, where an accumulating step is "applying the function", with z = id returning the final accumulated value when "there are no more xs":
foldl f a xs =~ foldr (\x r a-> r (f a x)) id xs a
Similarly, for finite lists,
foldr f a xs =~ foldl (\r x a-> r (f x a)) id xs a
And since the combining function gets to decide whether to continue or not, it is now possible to have left fold that can stop early:
foldlWhile t f a xs = foldr cons id xs a
where
cons x r a = if t x then r (f a x) else a
or a skipping left fold, foldlWhen t ..., with
cons x r a = if t x then r (f a x) else r a
etc.
I found a way using quite similar method to yours:
myzip = foldr step (const []) :: [a] -> [b] -> [(a,b)]
where step a f (b:bs) = (a,b):(f bs)
step a f [] = []
For the non-native Haskellers here, I've written a Scheme version of this algorithm to make it clearer what's actually happening:
> (define (zip lista listb)
((foldr (lambda (el func)
(lambda (a)
(if (empty? a)
empty
(cons (cons el (first a)) (func (rest a))))))
(lambda (a) empty)
lista) listb))
> (zip '(1 2 3 4) '(5 6 7 8))
(list (cons 1 5) (cons 2 6) (cons 3 7) (cons 4 8))
The foldr results in a function which, when applied to a list, will return the zip of the list folded over with the list given to the function. The Haskell hides the inner lambda because of lazy evaluation.
To break it down further:
Take zip on input: '(1 2 3)
The foldr func gets called with
el->3, func->(lambda (a) empty)
This expands to:
(lambda (a) (cons (cons el (first a)) (func (rest a))))
(lambda (a) (cons (cons 3 (first a)) ((lambda (a) empty) (rest a))))
If we were to return this now, we'd have a function which takes a list of one element
and returns the pair (3 element):
> (define f (lambda (a) (cons (cons 3 (first a)) ((lambda (a) empty) (rest a)))))
> (f (list 9))
(list (cons 3 9))
Continuing, foldr now calls func with
el->3, func->f ;using f for shorthand
(lambda (a) (cons (cons el (first a)) (func (rest a))))
(lambda (a) (cons (cons 2 (first a)) (f (rest a))))
This is a func which takes a list with two elements, now, and zips them with (list 2 3):
> (define g (lambda (a) (cons (cons 2 (first a)) (f (rest a)))))
> (g (list 9 1))
(list (cons 2 9) (cons 3 1))
What's happening?
(lambda (a) (cons (cons 2 (first a)) (f (rest a))))
a, in this case, is (list 9 1)
(cons (cons 2 (first (list 9 1))) (f (rest (list 9 1))))
(cons (cons 2 9) (f (list 1)))
And, as you recall, f zips its argument with 3.
And this continues etc...
The problem with all these solutions for zip is that they only fold over one list or the other, which can be a problem if both of them are "good producers", in the parlance of list fusion. What you actually need is a solution that folds over both lists. Fortunately, there is a paper about exactly that, called "Coroutining Folds with Hyperfunctions".
You need an auxiliary type, a hyperfunction, which is basically a function that takes another hyperfunction as its argument.
newtype H a b = H { invoke :: H b a -> b }
The hyperfunctions used here basically act like a "stack" of ordinary functions.
push :: (a -> b) -> H a b -> H a b
push f q = H $ \k -> f $ invoke k q
You also need a way to put two hyperfunctions together, end to end.
(.#.) :: H b c -> H a b -> H a c
f .#. g = H $ \k -> invoke f $ g .#. k
This is related to push by the law:
(push f x) .#. (push g y) = push (f . g) (x .#. y)
This turns out to be an associative operator, and this is the identity:
self :: H a a
self = H $ \k -> invoke k self
You also need something that disregards everything else on the "stack" and returns a specific value:
base :: b -> H a b
base b = H $ const b
And finally, you need a way to get a value out of a hyperfunction:
run :: H a a -> a
run q = invoke q self
run strings all of the pushed functions together, end to end, until it hits a base or loops infinitely.
So now you can fold both lists into hyperfunctions, using functions that pass information from one to the other, and assemble the final value.
zip xs ys = run $ foldr (\x h -> push (first x) h) (base []) xs .#. foldr (\y h -> push (second y) h) (base Nothing) ys where
first _ Nothing = []
first x (Just (y, xys)) = (x, y):xys
second y xys = Just (y, xys)
The reason why folding over both lists matters is because of something GHC does called list fusion, which is talked about in the GHC.Base module, but probably should be much more well-known. Being a good list producer and using build with foldr can prevent lots of useless production and immediate consumption of list elements, and can expose further optimizations.
I tried to understand this elegant solution myself, so I tried to derive the types and evaluation myself. So, we need to write a function:
zip xs ys = foldr step done xs ys
Here we need to derive step and done, whatever they are. Recall foldr's type, instantiated to lists:
foldr :: (a -> state -> state) -> state -> [a] -> state
However our foldr invocation must be instantiated to something like below, because we must accept not one, but two list arguments:
foldr :: (a -> ? -> ?) -> ? -> [a] -> [b] -> [(a,b)]
Because -> is right-associative, this is equivalent to:
foldr :: (a -> ? -> ?) -> ? -> [a] -> ([b] -> [(a,b)])
Our ([b] -> [(a,b)]) corresponds to state type variable in the original foldr type signature, therefore we must replace every occurrence of state with it:
foldr :: (a -> ([b] -> [(a,b)]) -> ([b] -> [(a,b)]))
-> ([b] -> [(a,b)])
-> [a]
-> ([b] -> [(a,b)])
This means that arguments that we pass to foldr must have the following types:
step :: a -> ([b] -> [(a,b)]) -> [b] -> [(a,b)]
done :: [b] -> [(a,b)]
xs :: [a]
ys :: [b]
Recall that foldr (+) 0 [1,2,3] expands to:
1 + (2 + (3 + 0))
Therefore if xs = [1,2,3] and ys = [4,5,6,7], our foldr invocation would expand to:
1 `step` (2 `step` (3 `step` done)) $ [4,5,6,7]
This means that our 1 `step` (2 `step` (3 `step` done)) construct must create a recursive function that would go through [4,5,6,7] and zip up the elements. (Keep in mind, that if one of the original lists is longer, the excess values are thrown away). IOW, our construct must have the type [b] -> [(a,b)].
3 `step` done is our base case, where done is an initial value, like 0 in foldr (+) 0 [1..3]. We don't want to zip anything after 3, because 3 is the final value of xs, so we must terminate the recursion. How do you terminate the recursion over list in the base case? You return empty list []. But recall done type signature:
done :: [b] -> [(a,b)]
Therefore we can't return just [], we must return a function that would ignore whatever it receives. Therefore use const:
done = const [] -- this is equivalent to done = \_ -> []
Now let's start figuring out what step should be. It combines a value of type a with a function of type [b] -> [(a,b)] and returns a function of type [b] -> [(a,b)].
In 3 `step` done, we know that the result value that would later go to our zipped list must be (3,6) (knowing from original xs and ys). Therefore 3 `step` done must evaluate into:
\(y:ys) -> (3,y) : done ys
Remember, we must return a function, inside which we somehow zip up the elements, the above code is what makes sense and typechecks.
Now that we assumed how exactly step should evaluate, let's continue the evaluation. Here's how all reduction steps in our foldr evaluation look like:
3 `step` done -- becomes
(\(y:ys) -> (3,y) : done ys)
2 `step` (\(y:ys) -> (3,y) : done ys) -- becomes
(\(y:ys) -> (2,y) : (\(y:ys) -> (3,y) : done ys) ys)
1 `step` (\(y:ys) -> (2,y) : (\(y:ys) -> (3,y) : done ys) ys) -- becomes
(\(y:ys) -> (1,y) : (\(y:ys) -> (2,y) : (\(y:ys) -> (3,y) : done ys) ys) ys)
The evaluation gives rise to this implementation of step (note that we account for ys running out of elements early by returning an empty list):
step x f = \[] -> []
step x f = \(y:ys) -> (x,y) : f ys
Thus, the full function zip is implemented as follows:
zip :: [a] -> [b] -> [(a,b)]
zip xs ys = foldr step done xs ys
where done = const []
step x f [] = []
step x f (y:ys) = (x,y) : f ys
P.S.: If you are inspired by elegance of folds, read Writing foldl using foldr and then Graham Hutton's A tutorial on the universality and expressiveness of fold.
A simple approach:
lZip, rZip :: Foldable t => [b] -> t a -> [(a, b)]
-- implement zip using fold?
lZip xs ys = reverse.fst $ foldl f ([],xs) ys
where f (zs, (y:ys)) x = ((x,y):zs, ys)
-- Or;
rZip xs ys = fst $ foldr f ([],reverse xs) ys
where f x (zs, (y:ys)) = ((x,y):zs, ys)

Resources