Lecture 2 — 2018-01-18

Higher-order functions

This lecture is written in literate Haskell; you can download the raw source.

We spent the class discussion list functions, using anonymous functions (lambdas, written \x1 x2 x3 ... -> e), with a focus on maps and folds. I meant to discuss graphs but didn’t get to it—I’ve got some notes at the bottom anyway.

Before I go into detail about folds, you should know how to turn on warnings in GHC:

{-# OPTIONS_GHC -Wall -fno-warn-unused-imports #-}

I turn off the unused imports warning, because it’s annoying and not really relevant for us. For this file, we’ll also turn off warnings about name shadowing.

{-# OPTIONS_GHC -fno-warn-name-shadowing #-}

In general, though, it’s better to leave that warning on.

module Lec02 where

import Prelude hiding (map, foldr, foldl) -- hide some things we'll define ourselves

import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set

Maps

We started by observing some patterns:

addOne :: [Int] -> [Int]
addOne [] = []
addOne (x:xs) = x+1 : addOne xs

double :: [Int] -> [Int]
double [] = []
double (x:xs) = 2*x : double xs

negateAll :: [Bool] -> [Bool]
negateAll [] = []
negateAll (b:bs) = not b : negateAll bs

And abstracting out a general framework:

map :: (a -> b) -> [a] -> [b]
map _ [] = []
map f (x:xs) = f x : map f xs

The map function is a higher-order function, because it’s a function that takes another function as its input. We can understand its behavior diagrammatically like so:

   :             :
  / \           / \
 1   :        f 1  :
    / \    =>     / \
   2   :        f 2  :
      / \           / \
     3  []        f 3  []

Higher-order functions are extremely powerful: they let us express whole patterns of computation in a single fell swoop. Once we’ve written map, we don’t need to ever write that kind of recursion manually again. Not only do we avoid silly errors in writing map-like functions, we also save time.

Folds

There’s some nice material on Wikipedia about folds.

There are two kinds of folds: rightwards folds and leftwards folds. They correspond to direct and accumulating recursion, respectively. Since direct is easier to understand, we looked at foldr first.

The folds we’ll define—foldr and foldl are already in the Prelude…

so we can hide them for the rest of this file.

We’ll need a few more imports below.

foldr

Here’s a rightward fold, a higher-order function that seems a bit opaque at first blush.

foldr :: (a -> b -> b) -> b -> [a] -> b
foldr _ b [] = b
foldr f b (a:as) = f a (foldr f b as)

We can understandfoldr using the following equation:

foldr f b [a1,...,an] = f a1 (f a2 (... (f an b) ...))

We can also understand foldr as replacing a list’s ‘spine’ with function applications, like so:

   :             f
  / \           / \
 1   :         1   f
    / \    =>     / \
   2   :         2   f
      / \           / \
     3  []         3   b

We defined a few different functions using foldr.

head :: [a] -> a
head = foldr (\a _ -> a) undefined 

product :: [Int] -> Int
product = foldr (*) 1

and, or :: [Bool] -> Bool
and = foldr (&&) True
or  = foldr (||) False

In general, a function defined like:

g [] = v
g (x:xs) = f x (g xs)

can be implemented using foldr as:

g = foldr f v

foldl

Leftward folds are like rightward folds but using a different pattern:

   :                f
  / \              / \
 1   :            f   3
    / \    =>    / \
   2   :        f   2
      / \      / \
     3  []    b   1

The code for a leftward fold looks more like the accumulator passing style functions we’ve already written.

foldl :: (b -> a -> b) -> b -> [a] -> b
foldl _ b [] = b
foldl f b (a:as) = foldl f (f b a) as

Correspondingly, foldl satisfies the following equation:

foldl f b [a1,...,an] = f (... (f (f b a1) a2) ...) an

We can use foldl to define the list reversal:

rev :: [a] -> [a]
rev = foldl (\acc x -> x:acc) []

We can also use it to easily define last:

last = foldl (\a b->b) undefined 

Finally, we can mechanically translate recursive accumulating functions defined like:

g xs = g' xs b

g' [] acc = acc
g' (x:xs) acc = g' xs (f x acc)

into leftward folds like:

g' = foldl f b

Graphs

We didn’t get a chance to apply our newfound prowess with maps and folds to working with maps and sets.

Haskell’s maps and set data types (in Data.Map and Data.Set, respectively) are opaque: we don’t get to know what constructors they have, so we have no choice but to use maps, folds, and other higher-order functions to work with them.

type Node = String
type Graph = Map Node (Set Node)

Note how we (a) simulataneously assign types to a number of values while (b) simultaneously defining those values.

a,b,c,d,e :: Node
[a,b,c,d,e] = ["a","b","c","d","e"]

You can also use tuples, as in:

f,g :: Node
(f,g) = ("f","g")

Next, we can define two graphs.

g1,g2 :: Graph
g1 = Map.fromList [(a, Set.fromList [b,c]),
                   (b, Set.fromList [a,d]),
                   (c, Set.fromList [a,d]),
                   (d, Set.fromList [b,c])]
g2 = Map.fromList [(a, Set.fromList [b,c]),
                   (b, Set.fromList [a,d]),
                   (c, Set.fromList [a,d]),
                   (d, Set.fromList [])]

These correspond to the following directed graphs:

a ↔ b
↕   ↕    g1
c ↔ d

a ↔ b
↕   ↓    g2
c → d

We can easily calculate the out-degree of each node:

outDegrees :: Graph -> Map Node Int
outDegrees = Map.map Set.size

And we can just as easily check that all nodes have out-degree one or more:

allDegreeOneOrMore :: Graph -> Bool
allDegreeOneOrMore = Map.foldr ((&&) . (>=1)) True . outDegrees

We can also write a function that takes a node and a graph and makes a new graph where every node has out-degree of at least one.

makeDegreeOne :: Node -> Graph -> Graph
makeDegreeOne n g = Map.insert n (Set.singleton n) g'
  where g' = Map.map connect g
        connect tgts =
          if Set.null tgts
          then Set.singleton n
          else tgts