Homework 4

Lambda calculus interpreter

This homework is written in literate Haskell; you can download the raw source to fill in yourself. You’re welcome to submit literate Haskell yourself, or to start fresh in a new file, literate or not.

Please submit homeworks via the DCI submission page.

NOTE: This homework will be due on Friday, October 2nd, since I didn’t post it until Saturday.

module Hw04 where

import Prelude hiding (succ,pred)

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

Problem 1: pure lambda calculus

We’ll just have variable names be strings.

type Id = String

The pure lambda calculus has three forms: variables, applications, and lambda abstractions.

data LCExpr = 
    LCVar Id
  | LCApp LCExpr LCExpr
  | LCLam Id LCExpr
  deriving (Show,Eq)

Write a function freeVars that collects the set of free variables in a given lambda calculus expression.

freeVars :: LCExpr -> Set Id
freeVars = undefined

Write a function wellScoped that determines whether or not a given lambda calculus is well scoped, i.e., there.

wellScoped :: LCExpr -> Bool
wellScoped = undefined

Here we’ve defined a simple, environment-based lambda calculus interpreter, just like we’ve looked at in class on Monday.

data LCValue = Closure Id LCExpr (Env LCValue) deriving Eq
type Env a = Map Id a

extend :: Env a -> Id -> a -> Env a
extend env x v = Map.insert x v env

evalLC :: Env LCValue -> LCExpr -> LCValue
evalLC env (LCVar x) = env ! x
evalLC env (LCApp e1 e2) = 
  case evalLC env e1 of
    Closure x e env' -> evalLC (extend env' x (evalLC env e2)) e
evalLC env (LCLam x e) = Closure x e env

runLC :: LCExpr -> LCValue
runLC = evalLC Map.empty

We’re going to implement some of the Church numeral material we’ve seen in class. Here are the initial definitions:

true  = LCLam "x" (LCLam "y" (LCVar "x"))
false = LCLam "x" (LCLam "y" (LCVar "y"))
cond  = LCLam "p" (LCLam "t" (LCLam "e" (LCApp (LCApp (LCVar "p") (LCVar "t")) (LCVar "f"))))

zero = LCLam "s" (LCLam "z" (LCVar "z"))
succ = LCLam "n" (LCLam "s" (LCLam "z" 
         (LCApp (LCVar "s") (LCApp (LCApp (LCVar "n") (LCVar "s")) (LCVar "z")))))

This is a little annoying. Surely we can make these kinds of definitions easier! Write a function lam that takes a list of variable names and a function body and produces a series of nested lambda expressions around that body. For example lam ["s","z"] (LCVar "z") should yield the value for zero.

If lam is called with an empty args list, it should just return the body.

lam :: [Id] -> LCExpr -> LCExpr
lam args body = undefined

Write a similar function, app, that takes a list of expressions and produces an appropriately nested application. For example, lam ["n","s","z"] (app [LCVar "s",app [LCVar "n",LCVar "s",LCVar "z"]]) should yield the value for succ.

What should app do when called with no arguments? Is there a value that’s generally ‘safe’ to return here?

app :: [LCExpr] -> LCExpr
app es = undefined

With these helper functions to hand, complete the following definitions for Church numerals. You can of course use any of the foregoing functions.

isZero, plus, times :: LCExpr
isZero = undefined
plus = undefined
times = undefined

Here is the Church encoding for pairs.

pair = lam ["a","b","c"] $ app $ map LCVar ["c","a","b"]
first = lam ["c"] $ app [LCVar "c", true]
second = lam ["c"]$ app [LCVar "c", false]

Now define the predecessor function, pred, and subtraction, sub.

pred, sub :: LCExpr
pred = undefined
sub = undefined

Problem 2: lambda calculus with primitives

You may have a headache from debugging your pure lambda calculus code—how do you know what number something is? In this problem, you’ll definie a lambda calculus interpreter that has numbers and booleans, too.

Here’s the new definition of values and expressions. Unfortunately, we can’t reuse the constructor names, so we’ll prefix these values and express with V and E, respectively.

data Value = 
    VClosure Id Expr (Env Value)
  | VNumber Int
  | VBoolean Bool

data Expr =
    EVar Id
  | ETrue
  | EFalse
  | EIf Expr Expr Expr
  | ENum Int
  | EIncr Expr
  | EDecr Expr
  | EIsZero Expr
  | EApp Expr Expr
  | ELam Id Expr
  deriving (Show, Eq)

Please define an evaluator for this extended language. If the user does something ‘wrong’—like try to apply a number like a function—then you should use the function error :: String -> a to signal an error. Your error message should clearly explain the problem: what type of value did you expect, and what did you get instead? (Soon we’ll define a type system that will rule out these errors entirely.)

eval :: Env Value -> Expr -> Value
eval = undefined

Write a function embed, that embeds the terms of the pure lambda calculus into our new, extended language.

embed :: LCExpr -> Expr
embed = undefined

Write functions toChurch and fromChurch in the Expr language that convert ENum numbers to and from Church numerals. You may want to use the Y combinator (defined below as y) to write a recursive function.

y :: Expr
y = ELam "f" $ EApp g g
  where g = ELam "x" $ EApp f (EApp x x)
        f = EVar "f"
        x = EVar "x"

For toChurch, you don’t need to worry about negative inputs. (But: given this impoverished language, what would you do if I sadistically required you to worry about them?)

toChurch :: Expr
toChurch = undefined
fromChurch :: Expr
fromChurch = undefined

Problem 3: substitution

The semantics for the lambda calculus we’ve used in class uses substitution, not environments. Let’s write an interpreter that uses substitution!

(a) 10 points

What should the type of the substitution function be? How does using substitution change the type of our evaluation function? Do we need to add new datatypes, drop old ones, or leave everything the same? Why or why not?

Think hard about this question before you do parts (b) and (c). Write down your thoughts, and then actually implement the function. Were you right?

fill in here

(b) 5 points

Implement the substitution function for the pure lambda calculus (LCExpr). Call it subst. You may assume that e is closed—there is no need to be capture-avoiding.

(c) 5 points

Implement a call-by-value interpreter for the pure lambda calculus (LCExpr) using substitution. Call it evalSubst. You can use error :: String -> a to signal an error if you need to.

(d) 5 points

What are the pros and cons of the two styles of evaluator we’ve written?

fill in here

(e) 5 points

What do you need to do to adapt your definition of evalSubst to use call-by-name evaluation? You may either write code or prose explaining what your code would do.

fill in here