Schani's Old Stuff

Introduction

I've written lots of software over the past years. Some of it was intended to be released in a nice package to the world at some point, some was even meant to be useful, but most of it was written because I was curious how it would turn out and/or because I was bored at the time. As it happens, I have released and continue to maintain a few projects, which you can find on my homepage, but there's also a lot of stuff that didn't make it, in most cases because I was too lazy to get it into a form fit for public consumption.

I still think that most of these pieces of software - some of them very simple, others not so - will be of interest to somebody, but since I'm still too lazy I have chosen to create this page as a place for my abandoned software.

Just because I put a project on this page doesn't mean that I don't care about it, or don't want to be bothered with it any more, though, so if you have any questions, comments, or even consider using some piece of this software for whatever purpose, don't hesitate to mail me.

Legal Conditions

All the code on this page is free software distributed under the terms of the GNU General Public Licence.

Contents

Puzzles and Games
A Minesweeper Solver
The 12 Coins Problem
Lisp/Scheme Interpreters
A Scheme Interpreter in Forth
A Scheme Interpreter in OCaml
A Scheme to Unlambda Compiler

Puzzles and Games

A Minesweeper Solver

Solving a Minesweeper configuration, meaning given a configuration, finding out which fields are certain to be mines and which are certain not to be, is really very easy. Here's an algorithm to do it:

This algorithm will solve all solvable Minesweeper configurations. Unfortunately, it's also very inefficient. For example, take this configuration:

-----------
-8-8-8-8-8-
-----------
-----------
-8-8-8-8-8-
-----------
-----------
-8-8-8-8-8-
-----------

The - signs are fields which are not yet visited, the 8s are visited fields with 8 mines in their neighbourhood. Although it's obvious that all unvisited fields contain mines, the above algorithm would have to try 2^84 combinations to find that out. Assuming you have a 10 GHz Pentium 6 and your implementation can generate and check each combination in only 10 cycles, you'll have to wait about 613 million years for the solution.

Even worse, it could be that there is no algorithm for solving a Minesweeper configuration which has better worst-case asymptotic performance than the one above. Richard Kaye has proven that determining whether a Minesweeper configuration is consistent, i.e., whether it could arise during normal play and does not contradict itself, is NP-complete. Note that that does not mean that solving a configuration is requires exponential time, but it does at least make it somewhat likely.

It's not surprising, then, that my solver doesn't solve all solvable configurations. For those that it does solve, it's reasonably efficient, though. It can solve an expert board (99 mines in 30x16 fields) from start to finish in less than one tenth of a second, if it's successful.

The solver works by making deductions about minimum and maximum numbers of mines in sets of fields, very similar to how I usually think when I play the game. Here's an example (a + signifies a known mine):

+33+
---+

Via the left 3 we know that the three unvisited fields contain exactly two mines, while via the right 3 we know that the two right unvisited fields contain exactly one mine. If we combine that information, we can conclude that the left unvisited field contains a mine, although we cannot say which one of the other two contains a mine.

In general, let's say we have a set N with |N| fields, about which we know that it contains at least Nl mines and at most Nu mines. We also have a set M with |M| fields, containing at least Ml mines and at most Mu mines.

We'll first consider the intersection I of the two sets, which contains all fields that are both in N as well as in M. How many mines does this set contain at a minimum? Assume N contains its minimum amount of mines, Nl. Also assume that as many of those mines as possible are in those fields that are not in the intersection set I, namely |N|-|I| (that's the number of fields in N but not in I). So, I must contain at least Nl-(|N|-|I|) mines. We can use the same argument for the set M and arrive at another lower bound of Ml-(|M|-|I|) mines. Note that both of these numbers could be zero, so our third lower bound is 0. The best lower bound we can give, therefore, is the largest of these three numbers.

Next we'll see what we can say about the maximum number of mines in the set I. One upper bound is the maximum number of mines in N, Nu. The other one is Mu. Of course, I cannot contain more mines than it contains fields, so the third upper bound is |I|. The best upper bound we can give is the lowest of these three numbers.

Having established lower and upper mine bounds Il and Iu for the intersection set I, we'll now consider the difference set D=N-M, which contains all fields in N which are not in M.

To establish its lower bound, assume that N contains as few mines as possible (Nl), and that as many of N's mines as possible are in the intersection I (that's the part of N that is not in D). We know this latter number, too, it's Iu, the maximum number of mines in I. That gives us a lower bound of Nl-Iu, which can, unfortunately, be negative, so the second lower bound is 0.

We can establish the upper bound very similarly: Assume that N contains as many mines as possible (Nu), and that as few mines as possible are in the intersection I (Il), giving an upper bound of Nu-Il, with the other upper bound being |D|, the number of fields in the difference set.

The algorithm my solver uses is this:

When the algorithm terminates, the list D will contain zero or more sets with lower and upper bounds. Of real interest are only those sets whose lower and upper bounds are equal and are also equal to the number of fields in the set, or equal to zero. If both bounds are equal to the number of fields in the set, we know that all fields contain mines. If both bounds are zero, none of them do.

The lower and upper bounds of the other sets can at best be interpreted as approximate probabilities for the presence of mines. If a set containing one field has a lower bound of 0 and an upper bound of 1, it is wrong to conclude that it has a 50% chance of containing a mine. An exhaustive algorithm might find that that field must contain a mine, for example. In fact, a program for finding the exact probabilities in all configurations must be at least as inefficient as a program for solving all solvable configurations (after all, solving a configuration is nothing else than finding the probabilities for only those fields which are certain to contain mines and for those which are certain not to, which are 100% and 0%, respectively).

To illustrate this point a bit further, here's a configuration my solver cannot solve:

++4-2
--++-
+6--3
++22+

After finishing its algorithm, my solver proclaims that the second field in the second row (the one directly above the 6) contains at least 0 mines and at most 1. While this is certainly true (the bounds my solver produces are always accurate, though not necessarily the tightest ones possible), the probability that that field contains a mine is nowhere near 50%. The exact probability is in fact 100%, meaning that field must contain a mine. You can easily verify this by examining the consequences of there being no mine in that field.

Obviously, there is room for improvement in my solver. One such improvement which would probably take care of most cases arising during solving random mine fields would be, in case the above algorithm fails to unearth some certain mines or clear fields, to go through all unvisited fields neighbouring at least one visited field and try what the consequences would be if there were a mine in that field, and what if there were not. If one of these two scenarios resulted in a trivial contradiction, the other scenario would inevitably reflect the truth (assuming, of course, that the whole configuration does not in itself contain a conflict). Note that if none of the two possibilities turn out to result in contradiction, no conclusion can be made.

Of course, that new solver would still not be able to solve all configurations, although it would take care of the example above.

Download

The 12 Coins Problem

The 12 coins problem can be stated as follows: You have 12 similar looking coins, 11 of which have exactly the same weight. The 12th coin is a counterfeit and has a different weight, but you don't know if it's lighter or heavier than the others. You have a scales and are allowed 3 weighings to determine the counterfeit coin.

This is a description of my solution. It turns out that there are analytical solutions which don't require the help of a computer and which extend to larger numbers of coins, but those are not the solution I found.

I figured out (or, rather, I hoped) that it might be possible to set up three weighings in advance and from the results determine the counterfeit coin. By "in advance" I mean that the configuration of the second weighing doesn't depend on the result of the first, etc. My instincts told me that in each of the weighings I should weight 4 coins against 4 others and leave the remaining 4 coins alone. Let's name the 12 coins "A" to "L" and set up the weighings like this:

  ABCDEFGHIJKL
1 000011112222
2 011100021222
3 101201202012

Line 1 is the configuration for the first weighing, line 2 for the second and 3 for the third. A "0" in a coin's column means that it isn't weighed in that round. A "1" means it's on the left scale and a "2" says it's on the right scale. Hence, according to this table, we first weigh EFGH against IJKL, then BCDI against HJKL, and finally ACFK against DGIL.

Now, let's say in our first weighing the left scale is heavier (we denote that as "1"), in the second one the right scale is heavier (denoted as "2") and in the third weighing they were level ("0"). Let's assume that the counterfeit is lighter than the other coins. That means it must have been on the right scale in the first weighing, on the left in the second and on the bench in the third, i.e., it should have the numbers "210" in its column. Referring to the table we note that there is no such coin. Let's assume that it was heavier, then. In this case it should have "120" in its columns, and indeed, coin H (and only coin H) fits our criteria.

The question is now, would we always be so lucky to find one, and only one, matching coin if we weighed according to this table? It turns out that there are three (very obvious) criteria that our table must fit for that to be the case:

As if by magic, the table above fits these criteria, as well as a fourth one:

This fourth criterion ensures the we can even tell whether the counterfeit is lighter or heaver (if one coin is never weighed, we might be able to tell it's counterfeit because all the others have the same weight, but we couldn't tell whether it's lighter or heavier).

The above table was calculated with my little program, which you can download below. It uses a simple brute-force approach, eventually trying out all possibilities. For only 12 coins this works very well and gives solutions instantly, but of course it doesn't scale.

Note that if you discard the fourth criterion you can extend the table with a coin which isn't weighed at all and you'd have a solution to the same problem with 13 coins.

Download

Lisp/Scheme Interpreters

When I learn a new programming language, the first program I write in that language is usually an interpreter for a small subset of Lisp or Scheme. I have found that to be a good way to quickly familiarize myself with most aspects of a new language. These are some of the results of my efforts.

A Scheme Interpreter in Forth

This is an interpreter for a really simple dynamically scoped Scheme dialect. It only runs with Gforth, because it uses Gforth's structs to implement its data structures. One of the more involved parts of this interpreter is the reader, where I had to do quite a lot of stack juggling to keep everything in line. It doesn't look very involved now but I remember spending quite some time thinking about the stack layout for the reader routines.

Download

A Scheme Interpreter in OCaml

This is a very efficient interpreter for a small statically scoped subset of Scheme. In the hopelessly contrived recursive Fibonacci benchmark it beats Guile by about a factor of 2.5. It operates by compiling Scheme code into an intermediate data structure which can be executed more efficiently. Most importantly, no symbol lookup needs to happen during execution. I think it's a very nice little piece of software, so I'll present the more important parts of it here.

The two main data types are lisp_expr, which describes all Scheme data (including uncompiled code, which is of course nothing else but lists), and lisp_code, which describes compiled code. We'll start with lisp_expr:

type lisp_expr =
    Nil
  | Cons of lisp_expr * lisp_expr
  | Int of int

This is simple enough. Nil is the empty list, a Cons is a list cell and an Int is an integer. We need integers so that the fib benchmark will run. It goes on:

  | Symbol of symbol

This is a symbol, which, as we'll see below, has a name. Now it gets more complicated, though:

  | Builtin of (lisp_expr array -> lisp_expr)

A builtin is a function that's built into the Scheme interpreter, hence the name. A more modern name would probably be "native function". For example, the function "+" for adding integers is a builtin. Builtins cannot be written in Scheme, but they can be passed around and stored in variables (i.e., they are first class values), that's why they need to be included in this type.

A builtin is simply a function taking an array of values (the arguments) and returning a value (the result).

  | Closure of lisp_code * (lisp_expr array list)

This, finally, is a Scheme function, complete with environment. The first part, of type lisp_code, is the code of the function. We'll see the definition of that type below. The second part is the environment of the function (or actually closure). If you're not familiar with closures and environments, here's a short introduction:

Let's say you have this function:

(lambda (x)
  (lambda (y)
    (+ x y)))

It's a function that takes one argument x and returns another function, or closure (a "closure" is what we call code with an environment which it needs to execute). You can call this resulting closure with another argument y and it'll give you the sum of the two arguments. Note that you don't need to remember the argument x you gave to the first function, because it's contained in the closure it returned. The value of this argument is therefore contained in the environment of the returned closure.

Of course environments can contain more than one value. Most importantly, environments can be deep, as this example illustrates:

(lambda (a b)
  (lambda (c d)
    (lambda (e f)
      (- (+ (- a b) (- c d)) (+ e f)))))

When you call this function you'll get a closure whose environment contains the arguments a and b. This closure, when called, returns yet another closure, whose environment contains the arguments c and d, but also a and b as well.

Let's say you called the function above with the arguments 1 and 2, and the resulting closure with 3 and 4. You'd get a closure whose environment is the list of arrays [ [| 3; 4 |]; [| 1; 2 |] ]. The most "recent" argument are always at the front of the list, that's why 3 and 4 are first. Note that the environment does not contain the names of the arguments. Instead, the compiler figures out automatically where in the environment it needs to look for the value of an argument. Note also that the closure does not specify how many arguments it takes, which means that the interpreter cannot catch the error of giving too many or too few arguments to a closure. This is only intentional as far as I was too lazy to make it any fancier.

Next are symbols, which are easy:

and symbol_value =
    Value of lisp_expr
and symbol = { name: string ; mutable value: symbol_value };;

A symbol has a name, obviously, but also a value. All symbols are stored in a global symbol table and a symbol's value is the value of the global variable with that name. Whenever the reader encounters a symbol, it looks it up in the symbol table and if it's not there, a new entry is made (that process is called "interning" the symbol). This means that whenever you use a new symbol you get a new global variable (whose default value is Nil), which is usually not what you want, but I was too lazy to change this. The easiest way would probably be to add an Undefined alternative to the symbol_value type, so that the interpreter can give an error message whenever an undefined global variable is referenced.

We now come to the definition of compiled code:

and lisp_code =
    Quote of lisp_expr

This is just a quoted expression, like 'a (which is syntactic sugar for (quote a).

  | Global of symbol

This is a reference to a global variable.

  | Global_set of symbol * lisp_code

This is code for setting the value of a global variable, the Scheme syntax for which is (define name value).

  | Var of int * int

This is a reference to a local variable, i.e., to a value in the current environment. The first of the two integers says how deep into the environment the interpreter must reach, while the second integer says which element in the resulting array is to be fetched. In the environment example above, for example, to get to the value of a, we'd have to take the second array and from that the first element, hence the numbers would be 1 and 0 (since the first element has number 0).

  | If of lisp_code * lisp_code * lisp_code

This is a simple conditional. The first lisp_code is the condition, the second is the code for the consequent and the third for the alternative.

  | Application of lisp_code * (lisp_code array)

This is a function application. The first lisp_code is supposed to evaluate to a function, i.e., either a builtin or a closure, and the array contains the code for the arguments.

  | Build_closure of lisp_code

This, finally, is closure-generating code, i.e., a lambda expression. Again, it doesn't say how many arguments the closure is supposed to take, which is neither an oversight nor a feature, but merely the result of my laziness.

Now that we're through with the data structures, we're ready to discuss the interpreter, which consists of the classical functions eval and apply. I won't discuss the compiler because it's not as pretty as the interpreter. The only really "complicated" thing in the compiler is keeping track of local symbols, so that it can know where in the environment the interpreter has to look for a variable value. Anyway, here's the interpreter:

let rec eval x e =

eval takes a lisp_code x and an environment e in which to execute x. For a top-level expression, this environment is of course the empty list. eval returns the result of the execution of the code, which is a lisp_expr.

  match x with
    Quote q -> q

Quoting an expression is really easy - just return it.

  | Global { value = Value v } -> v

Referencing a global variable simply means getting its value.

  | Global_set (s, c) -> s.value <- Value (eval c e) ; Nil

Setting a global variable, on the other hand, means setting its value (and returning Nil). The value it is set to is the result of executing the corresponding code in the current environment.

  | Var (depth, index) -> (nth e depth).(index)

Since we know exactly where to look for in the environment for a local variable, this is really easy. First we select the array out of the list and then we select the element out of the array.

  | If (cond, cons, alt) -> if eval cond e == Nil then
                              eval alt e
                            else
                              eval cons e

This is one of the two more complicated rules. First we evaluate the condition. If it's Nil, i.e., false, we evaluate the alternative, otherwise, i.e., if it's true, we evaluate the consequent.

  | Application (f, args) -> apply (eval f e)
                                   (Array.map (function a -> eval a e) args)

Applying a function means first evaluating the function and all its arguments, and then calling apply, which performs the application once we know the function and the value of its arguments. We'll investigate apply below (it's very simple).

  | Build_closure c -> Closure (c, e)

Building a closure just means putting its code and the current environment into a Closure.

Here's apply, which takes a function (in the form of a lisp_expr) and an array of arguments:

and apply f a =
  match f with
    Builtin b -> b a

The function can be a builtin, in which case we just use the native OCaml function application.

  | Closure(c, e) -> eval c (a :: e)

The function can also be a closure, in which case we need to make a new environment for it first, which really only means putting the argument array in front of the closure's existing environment. Then we evaluate its code in this new environment.

  | _ -> raise Hell;;

Applying anything else (like an integer) is an error.

Download

A Scheme to Unlambda Compiler

Unlambda is an obfuscated functional programming language. I have written a compiler for a small, pure subset of the Scheme programming language, which generates Unlambda code. Furthermore, I have implemented in this Scheme subset an interpreter for a very simple Lambda-calculus-like virtual machine, which makes it possible to overcome the exponential code growth resulting from abstraction elimination. The following is a description of the basic concepts of this Compiler/Interpreter pair:

The basic building blocks in the Unlambda programming language are the functions S, K, I, and the application operator ` (backtick). Translated to Scheme, the function I is

(lambda (x) x)

i.e., the identity function. The function K takes two arguments (all functions in Unlambda are curried, which means that K really takes one argument and returns a function which takes a second argument) and returns the first one:

(lambda (x y) x)

S is a little bit more complicated. It takes three arguments X, Y, Z and applies X to Z, then Y to Z and then the result of the former application to the result of the latter, i.e:

(lambda (x y z) ((x z) (y z)))

The application operator ` uses an infix syntax. It takes a function, an argument (which is, like every value in Unlambda, a function as well) and applies the function to the argument, i.e., `XY is the same in Unlambda as (X Y) is in Scheme.

Unlambda provides other primitives as well, which are mainly useful for I/O and as shortcuts for more complicated constructs.

One thing Unlambda completely lacks is a concept of variables. There is no lambda or let operator or anything else that would give a name (or anything similar) to a value. Luckily, it's possible to "emulate" the lambda operator with the functions S, K, and I, by a process called "Abstraction Elimination". It is described on the Unlambda Home Page, so I won't repeat it here. What I will repeat, though, is that it has the unfortunate side effect of blowing a program up by a factor roughly proportional to the deepest nesting depth of lambda operators, which is obviously a big problem. We will see later how it is possible to overcome it.

Abstraction elimination gives us the lambda operator with one argument, but apart from that, we have very little yet. The first thing we can do is to extend lambda to support more than one argument, like in Scheme. To do this, we simply curry all functions, i.e., transform them to functions with one argument, like this:

(lambda (x y z) body) => (lambda (x) (lambda (y) (lambda (z) body)))

Function calls must be transformed similarly:

(f x y z) => (((f x) y) z)

Next on the list is the let operator, which gives names to values. The let operator can be transformed into a lambda operator and an application:

(let ((x x-val) (y y-val)) body) => ((lambda (x y) body) x-val y-val)

The letrec operator allows the definition of recursive functions. Because its implementation is a bit unwieldy, I'll first discuss the simpler lambda* operator, which can be used to generate a single anonymous recursive function (lambda* is not a part of the Scheme programming language, but a feature of this dialect). As an example, here's a function for computing the factorial of a number:

(lambda* fac (n)
  (if (<= n 2)
    n
    (* n (fac (- n 1))))))

The name fac is only visible within the function itself. This function can be transformed to eliminate the lambda* operator to this semantically equivalent function:

((lambda (x) (x x))
 (lambda (fac n)
   (if (<= n 2)
     n
     (* n (fac fac (- n 1)))))))

Note that the upper lambda expression applies the function below to itself, thereby giving it a way to refer to itself. Also note that when the function calls itself recursively, it must again pass itself as an argument to itself. Note even further that this example would not run in standard Scheme, because Scheme does not curry. In Scheme, the function would have to look like this:

((lambda (x) (x x))
 (lambda (fac)
   (lambda (n)
     (if (<= n 2)
       n
       (* n ((fac fac) (- n 1))))))))

The main difference between lambda* and letrec is that the latter can introduce more than one function, each of which can reference each other. The principle for translation is the same as with lambda*, only that here each function must be passed all functions (including itself) as arguments. For example, the expression

(letrec ((fa (lambda (i)
               (fb (- i 1))))
	 (fb (lambda (i)
	       (fa (+ i 1)))))
  (fa 0))

is semantically equivalent to

(let ((fa (lambda (fa fb i)
            (fb fa fb (- i 1))))
      (fb (lambda (fa fb i)
            (fa fa fb (- i 1)))))
  (fa fa fb 0))

The resulting let can be translated to a lambda as described above.

The most important language part that remains is the conditional operator if and the booleans #t and #f. Unlambda's "native" booleans are the function I for true and V, which takes argument and always returns itself, for false. The Unlambda home page presents an if function for these booleans, which takes three arguments, the first one a boolean, i.e., either I or V. If it is true, the function returns the second argument, otherwise the third.

In a strict language like Scheme, as opposed to a lazy one like Haskell, if is not a function, however. Its second argument is only evaluated if the condition is true, the third only if it is false. To accomplish this, we have to delay these arguments and force only the resulting one. Thus, we transform the expression

(if condition consequent alternative)

to

((*if* condition
   (lambda (dummy) consequent)
   (lambda (dummy) alternative))
 *I*)

whereas *if* is the Unlambda if function and *I* the function I.

That's pretty much all there is to the language and the compiler. As an example of how complex data structures can be represented, I'll discuss how lists can be implemented. Lists in Scheme are constructed out of so called "cons" cells. Each such cell is a tuple with two elements, which are called the "car" and the "cdr". The function cons takes two arguments and constructs such a cell. It can be implemented like this:

(lambda (car cdr)
  (lambda (f)
    (f car cdr)))

In this implementation, a cell is nothing more than a function which takes another function and applies it to the car and the cdr. This is taken advantage of in the implementation of the functions car and cdr, each of which take a cell and return its car or cdr, respectively. Here is the function car:

(lambda (cell)
  (cell (lambda (car cdr)
          car)))

What's left is a way of representing the empty list (), which is not a cons cell. Applying car or cdr to it is illegal, so it is not supposed to give meaningful results in those cases (we don't do error handling). However, it can be tested for with the function null?, which returns #t if applied to the empty list, and #f if applied to a cons cell. Here is the empty list:

(lambda (f)
  #t)

The reason for this implementation only becomes apparent when seen in conjunction with the function null?:

(lambda (cell)
  (cell (lambda (car cdr)
          #f)))

If the argument cell is the empty list, applying it to whatever argument will return #t, which is exactly what we want. If it is a cell, however, the inner lambda takes care of returning the result #f.

Given bits (booleans) and a way of putting them together (lists) it's now easy to represent numbers, or any other data structure desired, so I'll not go into the details of how this can be done.

We now have a compiler translating a reasonable subset of the Scheme programming language to Unlambda. In theory, we can now program to our heart's delight, compile the program to Unlambda and see it run. In practice, however, we still have one serious problem: The Unlambda programs get much too big. A simple program which reads two binary numbers, represents them as lists of booleans (in binary representation), adds them, and outputs the resulting binary number, compiles to an Unlambda program about 18MB in size. The original Scheme code is less than 50 lines. Running the program on my 1GB RAM machine is impossible because it uses too much memory. Clearly something must be done.

As I have already mentioned in the introduction, the result of this code growth is the process of abstraction elimination. For every single increase in nested lambda depth, the generated code grows by a factor of about three, and not very much can be done about it, except to keep lambdas shallow.

An important observation about abstraction elimination is that if one uses only some pre-fabricated functions and just applies them to each other, the lambda depth does not increase beyond that of those functions. Another observation is that constructing lists (via cons) only uses pre-fabricated functions which are applied to each other. In other words, we can construct lists of arbitrary length and depth without going beyond a fixed, very shallow, lambda depth. The result is that Unlambda programs representing lists only grow linearly with relation to the size of the list, not exponentially.

Since a Scheme program is nothing but a list, we could in theory write a Scheme interpreter in Scheme, compile it to Unlambda, and then have a way of executing arbitrary Scheme programs in Unlambda without exponential growth. Of course, a full Scheme interpreter - even for our limited subset - would be far too big as an Unlambda program, but it is possible to translate Scheme to a very simple list representation, which can then be interpreted by an Unlambda program.

I have discussed above how to translate the most important Scheme language features into pure lambda calculus. Now I'll discuss how to transform lambda calculus into something more appropriate for direct interpretation.

An expression in pure lambda calculus can be of one out of three types:

The main problem with making this work in an interpreter is representing and looking up the lambda argument names. Fortunately, it is easy to recognize that the names can be done away with completely, if environments are represented in a list form, like in the Scheme in OCaml interpreter discussed above. In that case, the only piece of information that is necessary for a variable reference is how many lambda expressions outside of the reference the name was introduced. For example, in

(lambda (x) (lambda (y) (lambda (z) y)))

we can do away with the names altogether and replace the reference to y by the number 2, since y was introduced by the second lambda expression outward of the reference, giving

(lambda (lambda (lambda 2)))

Of course, my interpreter does not represent a lambda expression with the symbol lambda. Instead, each expression is represented as a cons cell (compiled to Unlambda functions, as detailed above), the car of which gives the type of the expression. To that end, it is a cons cell itself whose car and cdr are booleans, which encode the following expression types:

The first thing the eval function does is check of which type the expression it is fed is:

(lambda* eval (env expr)
  (if (car (car expr))
    (if (cdr (car expr))

In the case of a lambda expression, the cdr of the expression cell gives the body. All we have to do is construct a closure with this body and the current environment. My interpreter represents a closure as a cons cell whose car is the environment and whose cdr is the body, so the code for interpreting a lambda expression is simply

      (cons env (cdr expr))

Note that we do not have to tag this closure for being a closure, because in this interpreter, every value is a closure.

Next on the list are applications. The cdr of an application's expression cell is a cons cell whose car is the function and whose cdr is the argument, both of which must of course be evaluated. Hence, the first thing we do with an application is evaluate the function:

      (let ((fun (eval env (car (cdr expr)))))

The result (now in fun) is a closure. When applying a function to an argument, we must call eval with the function body and with an environment which includes the new argument. The rest of the environment is that of the closure in fun. The code looks like this:

        (eval (cons (eval env (cdr (cdr expr)))
                    (car fun))
              (cdr fun))))

What this code does is first evaluate the application argument (via the inner call to eval), then cons the result together with the function's environment to get the new environment, and then evaluate the function's body with this new environment.

The last lambda calculus expression type is the variable reference. As outlined above, a variable reference contains a number giving the index of the variable to get in the current environment list. Representing numbers as lists of booleans involves using the if special form, which adds lambda depth and blows up the interpreter. Encoding the number in the length of the list would result in additional size in the generated code, especially when dealing with deep lambda nesting, which is not uncommon.

The solution I chose encodes numbers in binary representation, but instead of using #t for one and #f for zero, I use the function cdr for one and I for zero. In other words, applying a digit to a list returns either the list, if the digit is "zero", or the list advanced by one element if the digit is "one". Applying such a binary number list to an environment list entails - if the number list is not empty - applying the first, least significant, "digit" to the list, and then applying the rest of the number list to the result twice, or the other way around. The code for the recursive function get, which performs this application, is this:

(lambda* get (env pos)
  (if (null? pos)
    env
    ((car pos) (get (get env (cdr pos)) (cdr pos)))))

Now that we have this function, implementing a variable reference is very easy. The cdr of the expression cell contains the number list, so all we have to do is supply the current environment and this list to get and take the car, i.e., the first list element, of the result:

    (if (cdr (car expr))
      (car (get env (cdr expr)))

Don't mind the if line - it checks for the second boolean in the expression type cell, in case the first boolean turns out to be false (this is the alternative path of the outermost if.

Last, but not least, we come to the native functions, the purpose of which I have not yet mentioned. While the first three expression types are sufficient to implement any function, the interpreter still lacks the ability to do input and output. Instead of putting this functionality directly into the interpreter, for example by creating a new expression type for each input/output function, and thereby blowing up the interpreter by a considerable amount, I decided to simply add the functionality to call a "native", i.e., non interpreted, function, which is directly embedded in the intermediate code. The code for this expression type looks a bit complicated, but it is really quite simple:

      (cons () ((cdr expr) (cons (cons #t #t) (cons (cons #f #t) ())))))))

The cdr of the expression cell contains the native function, so we apply it to some argument. Since most I/O function in Unlambda behave - apart from their side effect - like the identity function, and even a native function must return a result in the form of an interpretable closure, we pass the native function an expression cell for an interpretable identity function, namely the cell ((#t . #t) . ((#f . #t) . ())), which is what the function (lambda (x) x) looks like to the interpreter. Of course, the native function must not necessarily return this expression cell, but most do. Those which don't, which are functions returning booleans, checking, for example, for end-of-file, must nevertheless return valid expression cells. The outermost cons creates a closure from the expression cell returned by the native function, with an empty environment.

Finally, we're through. This minimalistic interpreter compiles to about 400KB of Unlambda code. The benefits are obvious when comparing the sizes of the directly compiled code versus interpreted code of more complicated programs. The abovementioned binary adding program, which is about 18MB in size when compiled directly, now comes to only 470KB, and that includes the interpreter. Furthermore, it consumes little memory and runs nicely - albeit slowly - on my machine.

Download


Schani's Homepage