Lecture 3 — 2015-09-09

Laziness, higher-order functions, and semantics

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

We started the class by talking about what BSTs are for, and how to figure out how to define insertBST in the first homework.

We also went over how to use the and function to write a bunch of tests for your code.

module Lec03 where

import Lec01 (Day(..),isWeekday,nextDay)

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

The code part of the lecture focused mainly on laziness and higher order functions.

incAll = map (+1)

test_empty = incAll [] == []
test_123 = incAll [1,2,3] == [2,3,4]

runTests = and [test_empty,test_123]

test_error = error "uh oh"

ignore _ = ()

diverge 0 = diverge 1
diverge n = diverge (n+1)

diverge' = diverge'

We defined our own version of ., like so:

compose :: (b -> c) -> (a -> b) -> a -> c
compose f g = \x -> f (g x)

We also used . to define a few functions without having to mention any of those pesky variable names:

isWeekend = not . isWeekday

postponeWeekday :: [Day] -> [Day]
postponeWeekday = 
  filter isWeekday . map nextDay

The remaining forty five minutes of class focused on syntax and semantics.

We defined a simple arithmetic language over the integers—I mistakenly said naturals at first—with few operations: addition, multiplication, and negation. Its grammar was like so:

m, n are Integers

e is an Expression ::=
    n
  | e1 plus e2
  | e1 times e2
  | negate e

In lecture I used the traditional mathematical notations for the operations. Here I’ll use prose to make it clear what’s syntax and what’s math.

We gave semantics to this syntax in two ways: denotationally and with a rewrite system.

The denotational semantics looked like so:

[[-]] : Expression -> Integer

[[n]]       = n
[[e1 plus e2]] = [[e1] + [[e2]]
[[e1 times e2]] = [[e1] * [[e2]]
[[negate e]] = - [[e]]

We interpreted each expression as the integer it evaluates to. Direct, succinct—this looks a lot like an interpreter for this arithmetic language!

The rewriting semantics was defined as an inductive series of inference rules, like so:

-> is a relation between Expressions and Expressions
   i.e. -> is a subset of 2^{Expr x Expr}

---------------- Plus
n plus  m -> n+m

---------------- Times
n times m -> n*m

--------------- Negate
negate n  -> -n

e1 -> e1'
------------------------- PlusLeft
e1 plus e2 -> e1' plus e2

e2 -> e2'
------------------------- PlusRight
e1 plus e2 -> e1 plus e2'

e1 -> e1'
--------------------------- TimesLeft
e1 times e2 -> e1' times e2

e2 -> e2'
--------------------------- TimesRight
e1 times e2 -> e1 times e2'

e -> e'
--------------------- NegateInner
negate e -> negate e'

We then constructed some derivations using this rewrite system. It’s less obvious what these have to do with implementation, but it gave us a clear notion of what precise steps happened to evaluate an expression.