Version 12 of A lambda calculus interpreter with arithmetic

Updated 2014-03-02 01:40:01 by pooryorick

Introduction

NEM 10 Sept 2006 (updated 2008-06-24): The lambda calculus is one of the most elegant, and earliest, models of computing around. Its simplicity makes it ideal as a language to implement a little interpreter, while it is equivalent in power to a universal Turing machine. The original lambda calculus consists of just three syntactic constructs:

Variables: x, y, z etc

Abstraction: (?<var>.<expr>)

Application: (<expr> <expr>)

Abstraction creates a lambda, which denotes a single-parameter anonymous function (similar to a proc with no name and only one parameter). Application supplies an argument to a lambda abstraction. Variables in the body of a lambda term are replaced by the argument to that lambda. We will omit the details of how evaluation takes place (Beta-reduction and Alpha-conversion), and instead use a slightly different evaluation strategy that works for what we want. We will also add primitive support for integers and arithmetic into our interpreter. You can actually encode integers using just lambda abstractions (via Church numerals) and basic arithmetic, but the encoding is very inefficient and a bit clumsy to use.

Writing an interpreter reveals a lot about how (computer) languages are given meaning. A sentence in a language doesn't have implicit meaning on its own. The meaning comes from the interpretation of the sentence. Thus, there are always two parts to defining a language:

  • Syntax describes the valid sentences of the language and how they can be constructed;
  • Semantics describes what those sentences are supposed to mean.

A third part is defining pragmatics, which refers to details of how such a language should be processed (e.g., what effects should be caused when interpreting something like Tcl's [puts $chan $msg]). We will define the syntax of our language shortly. The semantics will be given by our interpreter, which evaluates a term one step at a time, in a straight-forward manner. This interpreter defines a (small-step) operational semantics for our language.

Another important step is that we don't try and define the complete meaning of every possible term in the language. Instead, we define the meaning of the basic constructs in our language and allow these constructs to contain symbols/variables. The meaning of these symbols is application-dependent. Our interpreter is parameterised with an environment argument. This environment contains a mapping from user-defined symbols/variables to their definitions in terms of the constructs of the language. The meaning of any given sentence can thus be established by applying our evaluation function to try and remove any variable references from the sentence and reducing it to a simplified form whose meaning can be determined. Typed functional programming languages (e.g., Haskell or ML) often have features to expand the abstract syntax of the language (through datatypes), whereas object-oriented languages often strive for a simpler uniform syntax and rely heavily on environments (objects are environments). Of course, FP languages also make heavy use of environments, and OO languages do have syntax, so that's quite a crude characterisation.

In order to define our interpreter succinctly, we will write some simple code for algebraic types and pattern matching. You can skip this code.

proc datatype {name = args} { uplevel 1 [linsert $args 0 |] }
proc | {name args} {
    set body [list list $name]
    foreach p $args { append body " \$$p" }
    uplevel 1 [list proc $name $args $body]
}
proc match {value cases} {
    upvar 1 __env__ env
    foreach {pattern -> body} $cases {
        if {[matches $pattern $value env]} {
            return [uplevel 1 [list dict with __env__ $body]]
        }
    }
    error "unmatched value \"$value\""
}
proc matches {pattern value envVar} {
    upvar 1 $envVar env
    if {[llength $pattern] == [llength $value] &&
        [lindex $pattern 0] eq [lindex $value 0]} {
        foreach var [lrange $pattern 1 end] val [lrange $value 1 end] {
            dict set env $var $val
        }
        return 1
    }
    return 0
}

Abstract Syntax Trees

We can now define the abstract syntax of our language as a datatype. The abstract syntax of a language defines the structure of the basic "interesting" elements of our language, while ignoring the low-level details of syntax (such as parentheses and punctuation). The abstract syntax datatype typically forms a tree structure, where expressions can have sub-expressions. This tree structure is known as an abstract syntax tree (AST). Here is the AST for our simple language:

namespace eval term {
    namespace export *
    namespace ensemble create
    
    # Define the abstract syntax tree (AST) datatype of our language
    datatype Term = Lambda var body     ;# lambda abstractions (i.e. functions)
                  | Apply a b           ;# function application
                  | Var name            ;# variables
                  | IntLit i            ;# integer literals
                  | Add a b             ;# addition
                  | Sub a b             ;# subtraction
                  | Mul a b             ;# multiplication
                  | Div a b             ;# division
}

The first three of these constructors are all that is required for the traditional lambda calculus. We have added integer literals and some primitive arithmetic operations. We can construct some example terms now:

namespace path term
set add [Lambda x [Lambda y [Add [Var x] [Var y]]]] ;# (\x.(\y.x+y))
set sum [Apply [Apply $add [IntLit 12]] [IntLit 4]]

These are quite difficult to read, and a bit clumsy to construct by hand. However, this abstract datatype representation makes it very easy to compute terms and perform operations over them. For example, we can define a pretty-printer that displays a term in a more readable form:

proc term::print t {
    match $t {
        {Lambda param body} -> { return "\\$param.[print $body]" }
        {Apply f x}         -> { return "([print $f] [print $x])" }
        {Var name}          -> { return $name }
        {IntLit i}          -> { return $i }
        {Add a b}           -> { return "([print $a] + [print $b])" }
        {Sub a b}           -> { return "([print $a] - [print $b])" }
        {Mul a b}           -> { return "([print $a] * [print $b])" }
        {Div a b}           -> { return "([print $a] / [print $b])" }
    }
}
puts "sum = [term print $sum]"

Which prints something a bit more readable.

The Interpreter

We now come to the core of our language, the interpreter. The interpreter consists of a simple pair of mutually recursive functions: eval and apply (Tcl has them too). I find the simplicity and elegance of these functions breathtaking. (See SICP for more on eval and apply[L1 ]). Pattern matching makes the operation of this interpreter very clear:

proc term::eval {t {env ""}} {
    datatype Value = Closure env param body
    match $t {
        {Lambda param body} -> { Closure $env $param $body }
        {Apply f x}         -> { apply [eval $f $env] [eval $x $env] }
        {Var name}          -> { dict get $env $name }
        {IntLit i}          -> { return $i }
        {Add a b}           -> { expr {[eval $a $env] + [eval $b $env]} }
        {Sub a b}           -> { expr {[eval $a $env] - [eval $b $env]} }
        {Mul a b}           -> { expr {[eval $a $env] * [eval $b $env]} }
        {Div a b}           -> { expr {[eval $a $env] / [eval $b $env]} }
    }
}
proc term::apply {f x} {
    match $f {
        {Closure env param body} -> { eval $body [dict set env $param $x] }
    }    
}

Notice how lambda expressions are evaluated: first a lambda abstraction evaluates to a closure by simply capturing the current environment at the point of definition. Then when this closure is applied to an argument, the apply procedure simply restores the captured environment, binds the argument to the formal parameter and then evaluates the body in this new environment. This simple scheme is incredibly powerful. By playing around with the interpreter you can achieve a variety of different evaluation strategies (e.g. in the Apply case, try just passing $x unevaluated. What happens? Is this safe? If not, how could we make it safe?)

We can now start evaluating expressions in our little language:

% term eval $sum
16
% term eval [Mul [IntLit 2] [IntLit -4]]
-8

OK, that seems to work. Now, let's create a function that squares it's argument:

% set square [Lambda x [Mul [Var x] [Var x]]]
Lambda x {Mul {Var x} {Var x}}
% term eval [App $square [IntLit 4]]
16
% term eval [App $square [IntLit 20]] 
400

OK, let's get a bit more complicated -- we will create a curried function that takes a number and then returns a function that will add the original number to its argument. In other words [adder 1] will return a function that adds 1 to its argument:

% set adder [Lambda x [Lambda y [Add [Var x] [Var y]]]]
Lambda x {Lambda y {Add {Var x} {Var y}}}
% term eval [App [App $adder [IntLit 1]] [IntLit 12]]
13
% set add1 [term eval [App $adder [IntLit 1]]]
Closure {x 1} y {Add {Var x} {Var y}}
% term eval [App $add1 [IntLit 12]]
13

This is really quite sophisticated behaviour, and our interpreter is only a dozen or so lines!

Generic Operations over ASTs

You may have noticed that the print and eval routines are remarkably similar in the way they are written. This is not surprising: they both have to follow the recursive structure of the abstract syntax tree. We can define a generic fold operation over ASTs in much the same way that we can for lists. However, instead of folding a single operation over a list, we instead must fold a set of operations over the AST: one for each type of node we will visit. Rather than pass in an individual function for each AST node type (which would be clumsy and difficult to extend), we can instead pass in an ensemble command that has a sub-command for each type of node. Our fold function then simply recursively follows the structure of the AST and calls the appropriate callback for each node it encounters:

# Define a generic "fold" operation (catamorphism) over our AST datatype
proc term::fold {f z t} {
    match $t {
        {Lambda var body}   -> { $f lam $z $var $body }
        {Apply a b}         -> { $f app $z [fold $f $z $a] [fold $f $z $b] }
        {Var name}          -> { $f var $z $name }
        {IntLit i}          -> { $f int $z $i }
        {Add a b}           -> { $f add $z [fold $f $z $a] [fold $f $z $b] }
        {Sub a b}           -> { $f sub $z [fold $f $z $a] [fold $f $z $b] }
        {Mul a b}           -> { $f mul $z [fold $f $z $a] [fold $f $z $b] }
        {Div a b}           -> { $f div $z [fold $f $z $a] [fold $f $z $b] }
    }
}

The fold also allows an extra argument z to be passed around, much like fold on lists. This abstraction simplifies coding of the various commands, while also allowing us to separate the various processors (interpreters, pretty printers, type checkers, etc) from the specifics of how terms are represented. Here are our pretty-printer and interpreter written using the new fold mechanism:

# A pretty-printer
namespace eval pretty {
    namespace export *
    namespace ensemble create
    
    # We don't use the accumulator argument here. It could hold an indentation
    # level or something like that.
    proc lam {_ var body} { return "\\$var.[print $body]" }
    proc app {_ a b} { return "($a $b)" }
    proc var {_ name} { return $name }
    proc int {_ i} { return $i }
    proc add {_ a b} { return "($a + $b)" }
    proc sub {_ a b} { return "($a - $b)" }
    proc mul {_ a b} { return "($a * $b)" }
    proc div {_ a b} { return "($a / $b)" }
    
    proc print term { term fold pretty "" $term }
}
# Now define an interpreter
namespace eval interpreter {
    namespace export *
    namespace ensemble create
    
    datatype Value = Closure e v b
    
    proc lam {env var body} { Closure $env $var $body }
    proc app {env f x} { apply $f $x }
    proc var {env name} { dict get $env $name }
    proc int {env i} { return $i }
    proc add {env a b} { expr {$a + $b} }
    proc sub {env a b} { expr {$a - $b} }
    proc mul {env a b} { expr {$a * $b} }
    proc div {env a b} { expr {$a / $b} }
    
    proc apply {f x} {
        match $f {
            {Closure e p b}     -> { eval $b [dict set e $p $x] }
        }        
    }
    
    # Overall "eval" method
    proc eval {term {env ""}} { term fold interpreter $env $term }
}

With an AST and a generic fold operation, we can nicely separate the phases of our interpreter, and achieve loose coupling: each module depends only on the interfaces of the other modules, not the particular representations used. It should be noted that the same can be achieved in an OO framework. The Visitor pattern is another way of writing a generic fold for an AST, using method calls instead of datatypes and pattern matching. Both have advantages.

Parsing

The example wouldn't be complete without showing how to construct an AST from some concrete syntax. So here we define a simple recursive-descent parser for our language. I won't go into the details of how the parser is constructed here, as parsing is covered elsewhere on the wiki. The key thing is that each of the various parse routines constructs and returns a piece of abstract syntax, building up the tree through recursive calls during the parsing process. I have deliberately limited the syntax to make the parser simple.

namespace eval parser {
    namespace export *
    namespace ensemble create
    
    # Grammar:
    # expr ::= "(" appl ")"
    #        | \var.expr
    #        | intlit
    #        | var
    # appl ::= expr expr
    #        | expr op expr
        
    proc parse string { parse-expr string }
    
    proc parse-expr s {
        upvar 1 $s string
        set string [string trim $string]
        set char [string index $string 0]
        switch -glob $char {
            "("         { parse-appl string }
            {\\}        { parse-lambda string }
            {[-+0-9]}   { parse-int string }
            {[a-zA-Z]}  { term Var [parse-var string] }
            default     { error "unexpected char '$char'" }
        }
    }
    proc parse-appl s {
        upvar 1 $s string
        # Skip leading (
        set string [string range $string 1 end]
        set e1 [parse-expr string]
        if {[llength $e1] == 0} { error "expected expression" }
        set op [parse-op string]
        set e2 [parse-expr string]
        if {[llength $e2] == 0} { error "expected expression" }
        if {[string index $string 0] ne ")"} {
            error "expected ')'"
        }
        set string [string range $string 1 end]
        if {$op eq ""} {
            # Function application
            term Apply $e1 $e2
        } else {
            switch -exact $op {
                +       { term Add $e1 $e2 }
                -       { term Sub $e1 $e2 }
                *       { term Mul $e1 $e2 }
                /       { term Div $e1 $e2 }
            }
        }
    }
    proc parse-lambda s {
        upvar 1 $s string
        # Skip leading \\
        set string [string range $string 1 end]
        set var [parse-var string]
        if {[llength $var] == 0} { error "expected var" }
        regexp {\s*\.s*(.*)} $string -> string
        set body [parse-expr string]
        if {[llength $body] == 0} { error "expected body expr" }
        term Lambda $var $body
    }
    proc parse-var s {
        upvar 1 $s string
        regexp {^\s*([a-zA-Z0-9_]+)\s*(.*)$} $string -> var string
        return $var
    }
    proc parse-int s {
        upvar 1 $s string
        regexp {^\s*([-+]?\d+)\s*(.*)$} $string -> int string
        term IntLit $int
    }
    proc parse-op s {
        upvar 1 $s string
        set op ""
        regexp {^\s*([-+*/])\s*(.*)$} $string -> op string
        return $op
    }
}

An Interactive Interpreter

We now have all the elements needed to create a little interactive interpreter (equivalent to tclsh for our language). We do this by implenting a simple REPL: read-eval-print loop (where read means parse). We also add a short-cut that allows you to add definitions to the top-level environment (let foo = bar). Try it out!

proc prompt {str var} { 
    upvar 1 $var line
    puts -nonewline stdout "$str "
    flush stdout
    gets stdin line
}
unset env
set env [dict create]
while {[prompt "lambda>" code] >= 0} {
    set var it
    regexp {let ([a-zA-Z0-9_]+) = (.*)} $code -> var code
    if {![catch { interpreter eval [parser parse $code] $env } result]} {
        dict set env $var $result
    }
    puts "$var = $result"
}

A sample session:

lambda> let prod = \x.\y.(x*y)
prod = Closure {} x {Lambda y {Mul {Var x} {Var y}}}
lambda> let double = (prod 2)
double = Closure {x 2} y {Mul {Var x} {Var y}}
lambda> (double 2)
it = 4

Extensions

The interpreter presented here has a number of limitations. Here are some ideas for how to extend it, which I leave as exercises for interested readers:

  • Adapt the syntax and parser to allow leaving out some parentheses. In particular, take function application to be left-associative and define the shorthand that "(a b c d)" is expands to "(((a b) c) d)"
  • Closure creation currently captures every visible variable binding, which leads to large closures. Write a function to analyse the body of a function and decide what variables it actually uses (Note: be careful to handle parameters correctly). Hint: this can be written as a fold over the body term.
  • Write a partial evaluation function similar to eval. Such a function will have a type like Term -> Term, rather than eval's Term -> Value. (Hint: you may want to make Values be a subset of Terms).