Implementing `cycle` with a fold

I’m working through Real World Haskell, and Ch. 4 Ex. 10 asks the reader to implement any, cycle, words, and unlines using folds.

any, words, and unlines felt pretty doable.
any'l :: (Foldable t) => (a -> Bool) -> t a -> Bool
any'l f = foldl' (\acc -> (acc ||) . f) False

any'r :: (Foldable t) => (a -> Bool) -> t a -> Bool
any'r f = foldr ((||) . f) False

words'l :: String -> [String]
words'l s = [x | x <- foldl' g [] s, x /= ""]
  where
    g acc x
      | x == ' ' = acc ++ [""]
      | null acc = [[x]]
      | otherwise = init acc ++ [last acc ++ [x]]

words'r :: String -> [String]
words'r s = [x | x <- foldr g [] s, x /= ""]
  where
    g x acc
      | x == ' ' = "" : acc
      | null acc = [[x]]
      | otherwise = (x : head acc) : tail acc

unlines'l :: [String] -> String
unlines'l = foldl' (\acc x -> acc ++ x ++ "\n") []

unlines'r :: [String] -> String
unlines'r = foldr (\x -> ((x ++ "\n") ++)) []

However, cycle caused me some confusion.

I have some intuitions:

  • foldr wouldn’t work, as if, say, I want to support (take n) . cycle, I have to build the list from the left, and using foldr would make the list extend infinitely leftward, making it impossible to get the first n elements of the list.
  • Either recursion or an infinite list is a must, as any fold would otherwise terminate.
  • cycle seems to print out intermediate results, ad infinitum, even without me take-ing, but I don’t know if I can achieve that behavior with a fold.

I attempted implementations of cycle'l :: [a] -> [a], one using recursion:

cycle'l l = g
  where
    -- [1] is a throwaway value, obviously a code smell
    g = foldl' (\acc _ -> acc ++ l) g [1]

and one with an infinite list:

cycle'l l = foldl' (\acc _ -> acc ++ l) [] [1..]

However, in neither case does something like take 3 $ cycle'l [0] seem to terminate. Why is that?
How would I find a better approach?

1 Like

This is not an issue, because lists are lazy. foldr does build lists ‘from the left’ (if by that you mean that the first subexpression to be reduced when the entire fold is reduced is the one involving the leftmost element), but that doesn’t mean that an infinite suffix has to be fully computed before it’s used.

You do want foldr for this, as well as recursion. The best way to think about foldr is as specifying a homogeneous replacement for the (:) and [] constructors in the list you provide to it. Can you think of a way to express what cycle does in terms of replacing every (:) in the provided list with something, and replacing the [] in the provided list with something else?

2 Likes

Ah, I guess this was what I was missing, thanks! My intuition was that the first reduced subexpression would be from the right, based on the parentheses, but that’s not necessarily how a computer would do it :slight_smile: it makes sense that it’s built up from the left and the right side remains thunked until demanded.

My thinking is now that I want to repeatedly prepend to the list, hence the first arg would be (:).
The third arg would be the input list, since that list contains the values I want to prepend, in the correct order.
And since I’m not providing an infinite list, recursion is therefore required, and the second arg would suffice to simply be the result of the fold itself.

Landed on this:

cycle'r :: [a] -> [a]
cycle'r l = g
  where
    g = foldr (:) g l

which seems to do the business!

E.g. if l == [0, 1, 2] then the list would be built up as 0:(1:(2:(0:....))) andtake-ing would work.

I feel like it should be possible to write an impl for foldl', though my other thought is now, my foldl' equivalents didn’t work because (++) requires building up the entire list? Or is my assumption about (++) wrong here?

3 Likes

foldr works actually and in fact, it’s the “most correct” function to use here!

If you think about what cycle does, it really turns a regular linked list

(:) -> (:) -> (:) -> []
 |      |      |
 v      v      v
 1      2      3

into a cyclical list

 +----------------+
 |                |
 v                |
(:) -> (:) -> (:)-+
 |      |      |
 v      v      v
 1      2      3

So the way to do that is to keep all the (:) nodes intact and replace the final [] with the beginning of the list.
cyclicalList = foldr (:) cyclicalList originalList does exactly that because folds are constructor substitutions

3 Likes

If you expand the fold, your foldl' solution essentially becomes

cycle' l = ((([] ++ l) ++ l) ++ ...) ++ l

but now because the parentheses are placed left-associatively like that, in order to get the first element from that, you would need to look through that infinite tower of nested (++) to get to the left-most l (taking infinite time).

If you used a right fold as in cycle' l = foldr (\_ acc -> l ++ acc) [] [1..], it would actually work, as you would get

cycle' l = [] ++ (l ++ (l ++ (... ++ l)))

where to get the first element, you only need to look through the first (++) and the first l since (++) is lazy in its second argument.

(Although note that even though this version is semantically equivalent to the regular cycle implementation, it’s actually quite a bit less efficient and produces a worse memory layout since this won’t produce a cyclical list. It will just return an infinite lazy list where new arguments have to be forced every time)

3 Likes

Now I remember: cycle is usually written as

cycle xs = let ys = xs ++ ys in ys

But then xs ++ ys = foldr (:) ys xs