Chapter 10: Folding Lists

“How do we reduce the demands made on our quantitatively limited powers of reasoning?” ~ Edsger W. Dijkstra

10.1 Folds

In this chapter, we will:

  • Explain what folds are and how they work.

  • Detail the evaluation process of folds.

  • Walk through writing folding functions.

  • Introduce scans, functions that are related to folds.

10.2 Bringing you into the fold

foldr :: (a -> b -> b) -> b -> [a] -> b

10.4 Fold right

foldr f z l =
  case l of
    [] -> z
    (x:xs) -> f x (foldr f z xs)

foldr (+) 0 [1,2,3] ≡ ((+) 1 ((+) 2 ((+) 3 0)))

10.4.1 How foldr evaluates

One initially non-obvious aspect of folding is that it happens in two stages, traversal and folding. Traversal is the stage in which the fold recurses over the spine. Folding refers to the evaluation or reduction of the folding function applied to the values.

For foldr, traversal of the spine is conditional on f, and can stop early. Except for the first cons cell, which is forced because of the pattern match (x:xs) -> f x (foldr f z xs).

Our input function, f, has the type (a -> b -> b), where b represents the “rest of the fold”.

10.5 Fold left

foldl f z l =
  case l of
    [] -> z
    (x:xs) -> foldl f (f z x) xs

foldl (+) 0 [1,2,3] ≡ ((+) ((+) ((+) 0 1) 2) 3)

foldl forces traversal of the entire spine before it returns a value.

Our input function f has the type signature (b -> a -> b), where our first argument b represents the “rest of the fold”.

10.5.2 Exercises: Understanding folds

  1. foldr (*) 1 [1..5] Will return the same result as which of the following?

    1. flip (*) 1 [1..5]

      This isn’t equivalent to foldr (*) [1..5].

      There isn’t even a fold involved. Let’s see what happens when I run it, anyways.

      ·∾ flip (*) 1 [1..5]
      <interactive>:1:1: error:
          • Non type-variable argument in the constraint: Num [a]
            (Use FlexibleContexts to permit this)
          • When checking the inferred type
              it :: forall a. (Num a, Num [a], Enum a) => [a]
      

      We get a type error.

      The evaluation process for this expression should be similar to this:

      flip (*) 1 [1,2,3,4,5]
      
      (\f x y -> y `f` x) (*) 1 [1,2,3,4,5]
      
      (\x y -> y * x) 1 [1,2,3,4,5]
      
      (\y -> y * 1) [1,2,3,4,5]
      
      [1,2,3,4,5] * 1
      

      Let’s try running the partially reduced expression.

      ·∾ [1,2,3,4,5] * 1
      <interactive>:1:1: error:
          • Non type-variable argument in the constraint: Num [a]
            (Use FlexibleContexts to permit this)
          • When checking the inferred type
              it :: forall a. (Num a, Num [a]) => [a]
      

      If we run [1,2,3,4,5] * 1 we get an error, because the types signature of (*).

      ·∾ :type (*)
      (*) :: Num a => a -> a -> a
      

      As we can see, both arguments to (*) have to be of the same type, and they both have to have an instance of Num.

      [1,2,3,4,5] and 1 are not the same type, and :: Num a => [a] does not have an instance of Num (though the elements within the list do have an instance of Num).

      I found this error message hard to read, so I asked about it on IRC.

      justsomguy I have this expression [1,2,3,4,5] * 1. Since the * function takes two arguments of the same type, and [1,2,3,4,5] and 1 have different types, I get a type error. The error is Non type-variable argument in the constraint: Num [a]. I understand the “non type-variable argument” part, but what’s this about a constraint?

      geekosaur :t (*)

      lambdabot Num a => a -> a -> a

      geekosaur Basically, instead of simply failing it as incompatible types, ghc tries to promote 1 (numeric literals are wrapped in fromInteger or fromRational by the compiler) to the type of the other parameter.

      But then hits that error unless you turn on -XFlexibleContexts and then would hit the nonexistence of a Num instance for lists by default.

      Num is involved twice: once as a constraint on the type of (*), and a second time as a constraint on the type of fromInteger

      geekosaur :t fromInteger

      lambdabot Num a => Integer -> a

      geekosaur The behavior of numeric literals and the Num instance are documented in the Language Report; it’s not a ghc-specific thing. https://www.haskell.org/onlinereport/haskell2010/haskellch6.html#x13-1360006.4.1 and various links from that.

      If I use concrete types for the arguments to *, instead of leaving GHC to infer the types, the type mismatch error is more obvious.

      ·∾ ([1,2,3,4,5] :: [Int]) * (1 :: Int)
      
      <interactive>:9:27: error:
          • Couldn't match expected type ‘[Int]’ with actual type ‘Int’
          • In the second argument of ‘(*)’, namely ‘(1 :: Int)’
            In the expression: ([1, 2, 3, 4, 5] :: [Int]) * (1 :: Int)
            In an equation for ‘it’:
                it = ([1, 2, 3, 4, ....] :: [Int]) * (1 :: Int)
      
    2. foldl (flip (*)) 1 [1..5]

      This is equivalent.

      The evaluation is parenthesized differently, but because the result of x * y is equivalent to y * x, this expression also produces 120, just like our original expression.

      Parenthesization

      f x y = "(" ++ x ++ "*" ++ y ++ ")"
      foldr    f     "i" ["1","2","3","4","5"]  ==>  "(1*(2*(3*(4*(5*i)))))"
      foldl    f     "i" ["1","2","3","4","5"]  ==>  "(((((i*1)*2)*3)*4)*5)"
      foldl (flip f) "i" ["1","2","3","4","5"]  ==>  "(5*(4*(3*(2*(1*i)))))"
      

      Result in GHCi:

      ·∾ foldl (flip (*)) 1 [1,2,3,4,5]
      120
      
    3. foldl (*) 1 [1..5]

      Yes, this is equivalent. Here’s proof:

      ·∾ foldr (*) 1 [1..5]
      120
      
      ·∾ foldl (flip (*)) 1 [1..5]
      120
      
      ·∾ foldl (*) 1 [1..5]
      120
      
  1. Write out the evaluation steps for foldl (flip (*)) 1 [1..3]:

    foldl :: (b -> a -> b) -> b -> [a] -> b
    foldl f acc l =
    case l of
    [] -> acc
    (x:xs) -> foldl f (f acc x) xs

    foldl (flip (*)) 1 [1,2,3] =
    case [1,2,3] of
    [] -> 1
    (1:[2,3]) ->
    foldl (flip (*)) ((flip (*)) acc 1) [2,3] =
    case [2,3] of
    [] -> 1
    (2:[3]) ->
    foldl (flip (*)) ((flip (*)) ((flip (*)) acc 1) 2) [3] =
    case [3] of
    [] -> 1
    (3:[]) ->
    foldl (flip (*)) ((flip (*)) ((flip (*)) ((flip (*)) acc 1) 2) 3) [] =
    case [] of
    [] -> 1

    The fully accumulated expression looks like this…

    ((flip (*)) ((flip (*)) ((flip (*)) 1 1) 2) 3)

    If we write our function infix, the association is easier to see

    let
    f = flip (*)
    in
    (((1 `f` 1) `f` 2) `f` 3)

    We can reduce this to normal form, now, if we want…

    ((flip (*)) ((flip (*)) ((flip (*)) 1 1) 2) 3)
    ((flip (*)) ((flip (*)) 1 2) 3)
    ((flip (*)) 2 3)
    6
  1. One difference between foldr and foldl is:

    1. foldr, but not foldl, traverses the spine of a list from right to left.

      False. Both functions traverse the spine in the same direction.

      10.4.1 How foldr evaluates, paragraph 17, says:

      17a) One initially non-obvious aspect of folding is that it happens in two stages, traversal and folding. 17b) Traversal is the stage in which the fold recurses over the spine. 17c) Folding refers to the evaluation or reduction of the folding function applied to the values. 17d) All folds recurse over the spine in the same direction; the difference between left folds and right folds is in the association, or parenthesization, of the folding function and, thus, in which direction the folding or reduction proceeds.

      10.5 Fold left, paragraph 1, sentence b says:

      1b) Left folds traverse the spine in the same direction as right folds, but their folding process is left associative and proceeds in the opposite direction as that of ``foldr``.

      From 10.5.1 Associativity and folding:

      1b) As we’ve said, both folds traverse the spine in the same direction.

      3d) Right folds have to traverse the list outside-in, but the folding itself starts from the end of the list.

      How do I prove this is true, though? Can I create an experiment that demonstrates this to be true? What about an argument from the function definition?

    2. foldr, but not foldl, always forces the rest of the fold.

      This is false. Here is a counter-example.

      ·∾ foldr (\_ _ -> 9001) 0 [1..]
      9001
      

      The values 2:3:4:n are not evaluated.

    3. foldr, but not foldl, associates to the right.

      Yes, here’s proof!

      ·∾  f x y = "(" ++ x ++ "*" ++ y ++ ")"
      
      ·∾  foldr f "1" ["1","2","3","4","5"]
      "(1*(2*(3*(4*(5*1)))))"
      
      ·∾  foldl f "1" ["1","2","3","4","5"]
      "(((((1*1)*2)*3)*4)*5)"
      
    4. foldr, but not foldl, is recursive.

      No. Both functions must be recursive in order to traverse the spine of the list.

  1. Folds are catamorphisms, which means they are generally used to:

    1. Reduce structure.

      At least, that’s what the book says. Let me be specific. Here are some excerpts.

      10.1 Folds

      1b) Folds as a general concept are called catamorphisms. 1c) You’re familiar with the root “morphism” from polymorphism. 1d) “Cata-” means “down” or “against,” as in “catacombs.” 1e) Catamorphisms are a means of deconstructing data. 1f) If the spine of a list is the structure of a list, then a fold is what can reduce that structure. 1

      [1] Note that a catamorphism can break down the structure but that structure might be rebuilt, so to speak, during evaluation.

      10.11.2 Catamorphism

      1a) A catamorphism is a generalization of folds to arbitrary datatypes. 1b) Where a fold allows you to break down a list into an arbitrary datatype, a catamorphism is a means of breaking down the structure of any datatype. 1c) The ``bool :: a -> a -> Bool -> a`` function in ``Data.Bool`` is an example of a simple catamorphism for a simple, non-collection datatype. 1d) Similarly, ``maybe :: b -> (a -> b) -> Maybe a -> b`` is the catamorphism for Maybe. 1e) See if you can notice a pattern:

      data Bool = False | True
      bool :: a -> a -> Bool -> a
      
      data Maybe a = Nothing | Just a
      maybe :: b -> (a -> b) -> Maybe a -> b
      
      data Either a b = Left a | Right b
      either :: (a -> c) -> (b -> c) -> Either a b -> c
      

      However, wikipedia gives a different definition.

      In category theory the concept of catamorphism denotes the uniques homomorphism from an initial algebra into some other algebra.

      If I follow the link for homomorphism I get…

      A homomorphism is a structure-preserving map between two algebraic structures of the same type, that preserves the operations of the structures.

      So, wikipedia says that catamorphisms preserve structure, and HPFP says that they “are generally used to reduce structure”, but “that structure might be rebuilt during evaluation”.

      I personally consider the input function as another kind of structure, that replaces the list constructor (:) structure.

      However, I don’t think there’s anything about folding functions that forces us to use an input function that preserves the operations of the list of elements. I suppose it’s possible to argue that since the output must have the same type as the list elements, the operations of the type of those elements are retained.

      But, does it even make sense to characterize folding functions as catamorphisms in the first place?

    2. Expand structure.

    3. Render you catatonic.

    4. Generate infinite data structures.

  1. The following are simple folds very similar to what you’ve already seen, but each has at least one error. Please fix and test them in your REPL:

    1. foldr (++) ["woot", "WOOT", "woot"]

      ·∾ foldr (++) ["woot","WOOT","woot"]
      <interactive>:1:1: error:
          • No instance for (Show ([[String]] -> [String]))
              arising from a use of ‘print’
              (maybe you haven't applied a function to enough argumens?)
          • In a stmt of an interactive GHCi command: print it
      
      ·∾ -- This fold was missing an identity value
      
      ·∾ foldr (++) "" ["woot","WOOT","woot"]
      "wootWOOTwoot"
      
    2. foldr max [] "fear is the little death"

      The function max will try to produce the character with the smallest ordinal value. But the accumulator parameter is set to the empty list, [], instead of a character. So there will be a type error.

      ·∾ foldr max [] "fear is the little death"
      
      <interactive>:1:14: error:
          • Couldn't match type ‘Char’ with ‘[a]’
            Expected type: [[a]]
              Actual type: [Char]
          • In the third argument of ‘foldr’, namely
              ‘"fear is the little death"’
            In the expression: foldr max [] "fear is the little death"
            In an equation for ‘it’:
                it = foldr max [] "fear is the little death"
          • Relevant bindings include it :: [a] (bound at <interactive>:1:1)
      

      In order to fix this, we should make the accumulator a character. I’ve picked the char with the lowest ordinal value so it doesn’t become the result.

      ·∾ foldr max (minBound :: Char) "fear is the little death"
      't'
      
    3. foldr and True [False, True]

      I don’t remember what and does, let me look it up.

      ·∾ :type and
      and :: Foldable t => t Bool -> Bool
      

      So it takes a collection of bools and returns a bool. bool only takes one argument, but the input function to foldr must be of two arguments. So this won’t work.

      ·∾ foldr and True [False,True]
      
      <interactive>:14:7: error:
          • Couldn't match type ‘Bool’ with ‘Bool -> Bool’
            Expected type: t0 Bool -> Bool -> Bool
              Actual type: t0 Bool -> Bool
          • In the first argument of ‘foldr’, namely ‘and’
            In the expression: foldr and True [False, True]
            In an equation for ‘it’: it = foldr and True [False, True]
      
      <interactive>:14:17: error:
          • Couldn't match expected type ‘t0 Bool’ with actual type ‘Bool’
          • In the expression: False
            In the third argument of ‘foldr’, namely ‘[False, True]’
            In the expression: foldr and True [False, True]
      
      <interactive>:14:23: error:
          • Couldn't match expected type ‘t0 Bool’ with actual type ‘Bool’
          • In the expression: True
            In the third argument of ‘foldr’, namely ‘[False, True]’
            In the expression: foldr and True [False, True]
      

      So, I’ll write a new input function that takes two arguments, instead.

      ·∾ foldr (\x y -> x && y) True [False,True]
      False
      
    4. This one is more subtle than the previous.

      foldr (||) True [False, True]
      

      Can it ever return a different answer?

      This function will always return True, since the z value is True, and ((||) False True) returns True.

      ·∾ foldr (||) True [False,True]
      True
      ·∾ foldr (||) True [False,False,False]
      True
      ·∾ foldr (||) True [True,True,True]
      True
      

      If we change the z value to False, then it’s possible for this expression to return False, given the right input list.

      ·∾ foldr (||) False [True,True,True]
      True
      ·∾ foldr (||) False [True,True,False]
      True
      ·∾ foldr (||) False [False,False,False]
      False
      
    5. foldl ((++) . show) "" [1..5]

      The arguments to our input function are reversed. Using foldr instead of foldl will have the intended effect.

      ·∾ foldl ((++) . show) "" [1,2,3,4,5]
      <interactive>:31:25: error:
          • No instance for (Num [Char]) arising from the literal ‘1’
          • In the expression: 1
            In the third argument of ‘foldl’, namely ‘[1, 2, 3, 4, ....]’
            In the expression: foldl ((++) . show) "" [1, 2, 3, 4, ....]
      
      ·∾ ((++) . show) "" [1,2,3,4]
      <interactive>:33:19: error:
          • No instance for (Num Char) arising from the literal ‘1’
          • In the expression: 1
            In the second argument of ‘(++) . show’, namely ‘[1, 2, 3, 4]’
            In the expression: ((++) . show) "" [1, 2, 3, 4]
      
      ·∾ ((++) . show) [1,2,3,4] ""
      "[1,2,3,4]"
      
      ·∾ foldr ((++) . show) "" [1,2,3,4,5]
      "12345"
      
      ·∾ foldl (flip ((++) . show)) "" [1,2,3,4,5]
      "54321"
      
    6. foldr const 'a' [1..5]

      The type signature of foldr is…

      foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
      

      The b type variable is determined by the argument value we supply to our z parameter, 'a'.

      The value 'a' is a character.

      ·∾ :type 'a'
      'a' :: Char
      

      Therefore, the input function bound to f must return a character.

      But the first argument to our input function const is the first element of the list, 1.

      The full expression would be const 1 (const 2 (const 3 (const 4 (const 5 'a')))).

      const always returns its first argument.

      The return value of 1 :: Num a => a does not match the expected return type of Char. So we get a type error when GHC tries to infer a type that is both a Char, and has an instance of Num.

      ·∾ foldr const 'a' [1,2,3,4,5]
      
      <interactive>:52:18: error:
          • No instance for (Num Char) arising from the literal ‘1’
          • In the expression: 1
            In the third argument of ‘foldr’, namely ‘[1, 2, 3, 4, ....]’
            In the expression: foldr const 'a' [1, 2, 3, 4, ....]
      

      To fix this, we can change the 'a' to 0.

      ·∾ foldr const 0 [1,2,3,4,5]
      1
      

      Or we can flip const, so that it receives 'a' as it’s first argument.

      ·∾ foldr (flip const) 'a' [1,2,3,4,5]
      'a'
      

      Which evaluates like this

      (flip const)
        1
        ((flip const) 2 ((flip const) 3 ((flip const) 4 ((flip const) 5 'a' ))))
      
      (flip const)
        1
        ((flip const) 2 ((flip const) 3 ((flip const) 4 'a')))
      
      (flip const)
        1
        ((flip const) 2 ((flip const) 3 'a'))
      
      (flip const)
        1
        ((flip const) 2 'a')
      
      (flip const) 1 'a'
      
      'a'
      
    7. foldr const 0 "tacos"

    Let’s look at the type signature for foldr again.

    ·∾ :type foldr
     foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
    

    Now I’ll examine the types of each argument.

    ·∾ :type const
    const :: a -> b -> a
    
    ·∾ :type 0
    0 :: Num p => p
    
    ·∾ :type "tacos"
    "tacos" :: [Char]
    

    If I plug in the types to foldr’s type signature by hand, I get this.

    foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
    
    -- First I'll line it up
    
    foldr const 0 "tacos" ::     const :: (a -> b -> a)
                          ->         0 :: Num b => b
                          ->   "tacos" :: [Char]
    
    -- Now I'll plug in the types so that all occurences of them are substituted in
    -- a ~ Char
    -- b ~ Num b => b
    -- Foldable t => t ~ []
    foldr const 0 "tacos" ::
      Num b
      =>  (b -> Char -> b)
      ->  b
      ->  [Char]
    

    So looking at this type signature, const must return a Num a => a. The second argument to const must also be a Char. But the accumulator, which serves as the second argument to const, is a Char, instead.

    So I should get a type error when I run this, that tells me that Char does not have an instance of the Num typeclass. Let me try.

    ·∾ :type foldr const 0 "tacos"
    
    <interactive>:1:13: error:
        • No instance for (Num Char) arising from the literal ‘0’
        • In the second argument of ‘foldr’, namely ‘0’
          In the expression: foldr const 0 "tacos"
         value
    

    So now we have two options: implement an instance of Num for Char, or we can flip const.

    ·∾ foldr (flip const) 0 "tacos"
    0
    
    1. foldl (flip const) 0 "burritos"

      Now we need to unflip const :)

      ·∾ foldl (flip const) 0 "burritos"
      
      <interactive>:31:20: error:
          • No instance for (Num Char) arising from the literal ‘0’
          • In the second argument of ‘foldl’, namely ‘0’
            In the expression: foldl (flip const) 0 "burritos"
            In an equation for ‘it’: it = foldl (flip const) 0 "burritos"
      
      ·∾ foldl const 0 "burritos"
      0
      
    2. foldl (flip const) 'z' [1..5]

      ·∾ foldl (flip const) 'z' [1..5]
      <interactive>:34:25: error:
          • No instance for (Num Char) arising from the literal ‘1’
          • In the expression: 1
            In the third argument of ‘foldl’, namely ‘[1 .. 5]’
            In the expression: foldl (flip const) 'z' [1 .. 5]
      ·∾ foldl const 'z' [1..5]
      'z'
      

10.6.1 Exercises: Database processing

Let’s write some functions to process the following data:

import Data.Time

data DatabaseItem = DbString String
                  | DbNumber Integer
                  | DbDate UTCTime
                  deriving (Eq, Ord, Show)

theDatabase :: [DatabaseItem]
theDatabase =
  [ DbDate (UTCTime
            (fromGregorian 1911 5 1)
            (secondsToDiffTime 34123))
  , DbNumber 9001
  , DbString "Hello, world!"
  , DbDate (UTCTime
            (fromGregorian 1921 5 1)
            (secondsToDiffTime 34123))
  ]
  1. Write a function that filters for DbDate values and returns a list of the UTCTime values inside them.

    filterDbDate :: [DatabaseItem] -> [UTCTime]
    filterDbDate = undefined
    
    
    filterDbDate :: [DatabaseItem] -> [UTCTime]
    filterDbDate = foldr dbDateToUTC []
      where
        dbDateToUTC (DbDate t) b = t : b
        dbDateToUTC _          b = b
    
    
    
  2. Write a function that filters for DbNumber values and returns a list of the Integer values inside them.

    filterDbNumber :: [DatabaseItem] -> [Integer]
    filterDbNumber = undefined
    
    
    filterDbNumber :: [DatabaseItem] -> [Integer]
    filterDbNumber = foldr dbNumToI []
      where
        dbNumToI (DbNumber i) b = i : b
        dbNumToI _            b = b
    
    
    
  3. Write a function that gets the most recent date.

    mostRecent :: [DatabaseItem] -> UTCTime
    mostRecent = undefined
    
    
    mostRecent :: [DatabaseItem] -> UTCTime
    -- What if the list of DatabaseItems is empty?
    -- Should I change this to work on NonEmpty lists,
    -- or return a Maybe UTCTime, instead?
    mostRecent [] = error "empty list"
    mostRecent xs = maximum . filterDbDate $ xs
    
    
  4. Write a function that sums all of the DbNumber values.

    sumDb :: [DatabaseItem] -> Integer
    sumDb = undefined
    
    
    sumDb :: [DatabaseItem] -> Integer
    sumDb = sum . filterDbNumber
    
    
    
  5. Write a function that gets the average of the DbNumber values.

    -- You'll probably need to use fromIntegral
    -- to get from Integer to Double.
    avgDb :: [DatabaseItem] -> Double
    avgDb = undefined
    
    
    avgDb :: [DatabaseItem] -> Double
    avgDb db =
      dbSum / dbLen
      where
        dbSum = fromIntegral (sumDb db)
        dbLen = fromIntegral (length $ filterDbNumber db)
    

10.7 Folding and evaluation

The relationship between foldr and foldl is such that foldr f z xsfoldl (flip f) z (reverse xs), but only for finite lists.

10.9 Scans

scanr f z l =
  case l of
    [] -> [z]
    (x:xs) -> foldr f z l : scan f z xs

scanl f z l =
  z : (case l of
        [] -> z
        (x:xs) -> scanl f (f z x) xs)

10.9.2 Scans exercises

fibs = 1 : scanl (+) 1 fibs
  1. Modify your fibs function to only return the first 20 Fibonacci numbers.

  2. Modify fibs to return the Fibonacci numbers that are less than 100.

  3. Try to write the factorial function from Chapter 8 as a scan.

    You’ll want scanl again, and your start value will be 1. Warning: this will also generate an infinite list, so you may want to pass it through a take function or similar.

I feel tired and unmotivated, so here’s the whole thing in one file, without any explanation.

#!/usr/bin/env stack
-- stack script --resolver lts-18.26 --package hspec
module Scans where
import Test.Hspec


fibs = 1 : scanl (+) 1 fibs

twentyFibs = take 20 fibs

fibsUnderOneHundred = takeWhile (<100) fibs

fact n = last (scanl (*) 1 [1..n])


main = hspec $ do
  describe "fibs" $ do
    it "first ten fibs" $ do
      take 10 fibs `shouldBe` [1,1,2,3,5,8,13,21,34,55]
    it "first twenty fibs" $ do
      twentyFibs `shouldBe`
        [1,1,2,3,5,8,13,21,34,55,89,144,233,377,610,987,1597,2584,4181,6765]
    it "fibsUnderOneHundred" $ do
      takeWhile (<100) fibs `shouldBe` [1,1,2,3,5,8,13,21,34,55,89]
    it "fact" $ do
      fact 3 `shouldBe` 6
      fact 9 `shouldBe` product [1..9]

10.10 Chapter exercises

10.10.1 Warm-up and review

For the following set of exercises, you are not expected to use folds. These are intended to review material from previous chapters. Feel free to use any syntax or structure from previous chapters that seems appropriate.

  1. Given the following sets of consonants and vowels:

    stops  = "pbtdkg"
    vowels = "aeiou"
    
    1. Write a function that takes inputs from stops and vowels and makes 3-tuples of all possible stop-vowel-stop combinations. These will not all correspond to real words in English, although the stop-vowel-stop pattern is common enough that many of them will.

    2. Modify that function so that it only returns the combinations that begin with a p.

    3. Now set up lists of nouns and verbs (instead of stops and vowels), and modify the function to make tuples representing possible noun-verb-noun sentences.

    
    stops  = ['p','b','t','d','k','g']
    vowels = ['a','e','i','o','u']
    
    -- 1a
    sts = [(s,v,s') | s <- stops, v <- vowels, s' <- stops]
    
    -- 1b
    stsp = [(s,v,s') | s <- stops, v <- vowels, s' <- stops, s == 'p']
    
    -- 1c
    nouns = ["house","car","banana"]
    verbs = ["build","drive","peel"]
    
    nvn = [(n,v,n') | n <- nouns, v <- verbs, n' <- nouns]
    
    
  2. What does the following mystery function do? What is its type? Try to get a good sense of what it does before you test it in the REPL to verify it:

    seekritFunc x =
      div
        (sum (map length (words x)))
        (length (words x))
    
    
    seekritFunc x =
      div (sum (map length (words x)))
          (length (words x))
    
    avgWordLength x = word_lengths `div` word_count
      where
        all_words    = words x
        word_lengths = sum . map length $ all_words
        word_count   = length all_words
    
    
  3. We’d really like the answer to be more precise. Can you rewrite that using fractional division?

    
    avgWordLengthFrac x = word_lengths / word_count
      where
        all_words    = words x
        word_lengths = fromIntegral $ sum . map length $ all_words
        word_count   = fromIntegral $ length all_words
    

10.10.2 Rewriting functions using folds

In the previous chapter, you wrote these functions using direct recursion over lists. The goal now is to rewrite them using folds. Where possible, to gain a deeper understanding of folding, try rewriting the fold version so that it is point-free.

Point-free versions of these functions written with a fold should look like this:

myFunc = foldr f z

So, for example, with the and function:

-- direct recursion, not using &&
myAnd :: [Bool] -> Bool
myAnd [] = True
myAnd (x:xs) =
  if x == False
  then False
  else myAnd xs

-- direct recursion, using &&
myAnd :: [Bool] -> Bool
myAnd [] = True
myAnd (x:xs) = x && myAnd xs

-- fold, not point-free
myAnd :: [Bool] -> Bool
myAnd = foldr
  (\a b ->
    if a == False
    then False
    else b) True

-- fold, both myAnd and the folding
-- function are point-free now
myAnd :: [Bool] -> Bool
myAnd = foldr (&&) True

The goal here is to converge on the final version where possible.

You don’t need to write all variations for each example, but the more variations you write, the deeper your understanding of these functions will become.

  1. myOr returns True if any Bool in the list is True:

    myOr :: [Bool] -> Bool
    myOr = undefined
    

    Here is my attempt:

    
    myOr :: [Bool] -> Bool
    myOr = foldr (||) False
    
    
  2. myAny returns True if a -> Bool applied to any of the values in the list returns True:

    myAny :: (a -> Bool) -> [a] -> Bool
    myAny = undefined
    

    Example for validating myAny:

    Prelude> myAny even [1, 3, 5]
    False
    Prelude> myAny odd [1, 3, 5]
    True
    

    Here is my attempt:

    
    myAny :: (a -> Bool) -> [a] -> Bool
    myAny f = foldr (\x xs -> f x || xs) False
    
    
  3. Write two versions of myElem. One version should use folding and the other should use any:

    myElem :: Eq a => a -> [a] -> Bool
    
    Prelude> myElem 1 [1..10]
    True
    Prelude> myElem 1 [2..10]
    False
    

    Here is my attempt:

    
    myElem :: Eq a => a -> [a] -> Bool
    myElem e = foldr (\x xs -> x == e || xs) False
    
    
  4. Implement myReverse. Don’t worry about trying to make it lazy:

    myReverse :: [a] -> [a]
    myReverse = undefined
    
    Prelude> myReverse "blah"
    "halb"
    Prelude> myReverse [1..5]
    [5,4,3,2,1]
    

    Here is my attempt:

    
    myReverse :: [a] -> [a]
    myReverse = foldl (flip (:)) []
    
    
  5. Write myMap in terms of foldr. It should have the same behavior as the built-in map:

    myMap :: (a -> b) -> [a] -> [b]
    myMap = undefined
    

    Here is my attempt:

    
    myMap :: (a -> b) -> [a] -> [b]
    myMap f = foldr ((:) . f) []
    
    
  6. Write myFilter in terms of foldr. It should have the same behavior as the built-in filter:

    myFilter :: (a -> Bool) -> [a] -> [a]
    myFilter = undefined
    

    Here is my attempt:

    
    myFilter :: (a -> Bool) -> [a] -> [a]
    myFilter f =
      foldr (\x xs -> if f x == True
                      then x : xs
                      else xs) []
    
    
  7. squish flattens a list of lists into a list:

    squish :: [[a]] -> [a]
    squish = undefined
    

    Here is my attempt:

    
    squish :: [[a]] -> [a]
    squish = foldr (++) []
    
    
  8. squishMap maps a function over a list and concatenates the result:

    squishMap :: (a -> [b]) -> [a] -> [b]
    squishMap = undefined
    
    Prelude> squishMap (\x -> [1, x, 3]) [2]
    [1,2,3]
    
    Prelude> f x = "WO " ++ [x] ++ " OT "
    
    Prelude> squishMap f "blah"
    "WO b OT WO l OT WO a OT WO h OT "
    

    Here is my attempt:

    
    squishMap :: (a -> [b]) -> [a] -> [b]
    squishMap f = squish . myMap f
    
    
  9. squishAgain flattens a list of lists into a list. This time, re-use the squishMap function:

    squishAgain :: [[a]] -> [a]
    squishAgain = undefined
    

    Here is my attempt:

    
    squishAgain :: [[a]] -> [a]
    squishAgain = squishMap id
    
    
  10. myMaximumBy takes a comparison function and a list and returns the greatest element of the list based on the last value that the comparison returns GT for:

    myMaximumBy :: (a -> a -> Ordering) -> [a] -> a
    myMaximumBy = undefined
    
    Prelude> myMaximumBy (\_ _ -> GT) [1..10]
    1
    Prelude> myMaximumBy (\_ _ -> LT) [1..10]
    10
    Prelude> myMaximumBy compare [1..10]
    10
    

Here is my attempt:


-- I could reutrn mempty if a had a constraint of Monoid, but
-- according to this type signature, I have to throw an exception
-- for empty lists.
myMaximumBy :: (a -> a -> Ordering) -> [a] -> a
myMaximumBy f = foldl1 (\x y -> case f x y of { GT -> x; _ -> y })

  1. myMinimumBy takes a comparison function and a list and returns the least element of the list based on the last value that the comparison returns LT for:

    myMinimumBy :: (a -> a -> Ordering) -> [a] -> a
    myMinimumBy = undefined
    
    Prelude> myMinimumBy (\_ _ -> GT) [1..10]
    10
    Prelude> myMinimumBy (\_ _ -> LT) [1..10]
    1
    Prelude> myMinimumBy compare [1..10]
    1
    

Here is my attempt: