data Expr = Atom String | List [Expr] instance Show Expr where show = \case Atom s -> s List xs -> "(" ++ unwords (show <$> xs) ++ ")"
Lisp
McCarthy’s classic 1960 paper introducing Lisp is life-changing. Paul Graham’s homage The Roots of Lisp [PDF] to the original paper is more accessible, and corrects bugs.
Lisp features prominently in the history of functional programming languages, though any language with garbage collection owes at least a small debt to Lisp.
We’ll build a Lisp interpreter based on Graham’s paper:
For the command-line version, if it appears that an expression is incomplete, rather than complain immediately, our interpreter asks for another line. This feature requires importing the Parsec library’s Error module.
Tree Processor
Lisp should really be called Trep. Lisp does not process lists, but rather
binary trees built from dotted pairs. Often, a Lisp tree only grows to the
right and terminates in a special nil
atom, so it resembles a list. We can
play the same trick in Haskell by removing type
checking.
Haskell is more deserving of the title "list processor" because its lists are
true singly-linked lists, and the language encourages their use thanks to
extensive library support and notation such as [1, 2, 3]
and (h:t)
.
This isn’t necessarily a good thing:
lists are less general than
trees because monoids are fussier than magmas.
Indeed, Haskell programmers often replace lists with trees despite the
inconvenience. For example, the ShowS
difference lists replace lists of
characters with a tree of functions. This avoids slow concatenation, but the
notation is less natural and lose the ability to inspect data because functions
are opaque.
I’d like to experiment with a modified Haskell based on trees instead of lists, but I’ll do that some other time. Our Lisp implementation here will be list-based, which is fitting for an alleged list processing language. In particular, we ignore the dotted pair, which is fine as our goal is only to implement enough to get Graham’s code working.
Seven Primitives
The seven primitive operators look the part. Our implementation even avoids
recursion thanks to foldr
.
prim go = \cases "quote" [x] -> pure x "atom" [Atom _ ] -> yes "atom" [List []] -> yes "atom" _ -> no "eq" [Atom x, Atom y] | x == y -> yes "eq" [List [], List []] -> yes "eq" [_, _] -> no "car" [List (h : _)] -> pure h "cdr" [List (_ : t)] -> pure $ List t "cons" [h, List t] -> pure $ List (h : t) "cond" conds -> foldr evcon Nothing conds where evcon (List [h, t]) other = case go h of Nothing -> Nothing Just (Atom "t") -> go t _ -> other evcon _ _ = Nothing yes = pure $ Atom "t" no = pure $ List []
We expect the passed go
function to evaluate an expression so that cond
can
determine which branch to take.
Eval
Our eval
function shows how the primitives fit into the language.
We see that as well as cond
, the quote
primitve must also be lazy.
The label
operator defines a new symbol to add to the environment. If it
appears at the top level we return a new binding along with the empty string.
If it appears elsewhere, we only return the empty string. This is probably for
the best, as it might be confusing to allow new symbol definitions deep within
a complex computation.
We also handle lambda
and list
here.
For lambda
, we add argument bindings to the environment before recursing.
eval env = \case List [Atom "label", Atom s, e] -> lbl s e List (Atom "defun" : Atom s : etc) -> lbl s $ List $ Atom "lambda" : etc x -> (id,) <$> go x where lbl s e = pure (((s, e):), Atom "") go = \case Atom s | Just b <- lookup s env -> pure b List as -> case as of Atom "lambda" : List args : body : t -> do binds <- zip (fromAtom <$> args) <$> mapM go t snd <$> eval (binds ++ env) body Atom "list" : etc -> List <$> mapM go etc Atom h : t | Just b <- lookup h env -> case b of List as -> go $ List $ as ++ t h -> go $ List $ h : t | otherwise -> prim go h =<< (if isLazy h then pure else mapM go) t _ -> Nothing fromAtom (Atom x) = x isLazy "cond" = True isLazy "quote" = True isLazy _ = False
Parser
We load our tiny parser library:
jsEval "curl_module('../compiler/Charser.ob')" import Charser
A simple parser suits Lisp’s simple grammar:
-- Whitespace and comments. ws = many $ sat isSpace <|> char ';' <* many (sat (/= '\n')) expr :: Charser Expr expr = atom <|> list <|> quot where atom = Atom <$> some (alphaNumChar <|> char '.') <* ws list = ch '(' *> (List <$> many expr) <* ch ')' quot = ch '\'' *> (List . (Atom "quote" :) . (: []) <$> expr) ch c = char c <* ws
Next, the interpret
function runs a given Lisp program. It adds any new
bindings to the environment as it proceeds, and calls a given function out
for every evaluated expression or error.
interpret out env0 src = case parse (ws *> many expr <* eof) "" src of Left e -> out ("parse error: " ++ e ++ "\n") *> pure env0 Right es -> foldM run env0 es where run env x = case eval env x of Nothing -> out "?" *> pure env Just (f, r) -> out (show r) *> pure (f env)
Our first use will be to preload definitions like (defun cadr (x) (cdr (car
x)))
from caar
to cddddr
.
cadrDefs = [concat ["(defun c", s, "r (x) (c", [h], "r (c", t, "r x)))"] | n <- [2..4], s@(h:t) <- replicateM n "ad"] putStr $ unlines cadrDefs Just preload = interpret Just [] $ concat cadrDefs
Lastly, we hook up the "Run" button on this webpage to our interpreter:
runner = do src <- jsEval "input.value;" jsEval "output.value = '';" interpret out preload src where out s = unless (null s) do jsEval $ "output.value += " ++ show s ++ "+ '\\n';" pure () jsEval [r|evalB.addEventListener("click", (ev) => { repl.run("chat", ["Main"], "runner"); });|]
That’s all! We have enough to run the code in Graham’s article.
A Bigger Surprise
McCarthy’s eval
function must have been astonishing for its time. Graham
calls it The Surprise, which is why we labeled the button "Surprise Me!".
But if surprise is inversely proportional to self-interpreter simplicity and size, then prepare to be amazed by Mogensen’s one-line self-interpreter in lambda calculus:
(λf.(λx.f(xx))(λx.f(xx)))(λem.m(λx.x)(λmn.em(en))(λmv.e(mv)))
The indelible impact of Lisp
The spirit of Lisp lives on in languages with modern conveniences.
Haskell is a fashionable five-star high-tech luxurious language, but stripping away its contemporary furnishings reveals a humble core surprisingly similar to Lisp. For example, take a typical function from Paul Graham’s On Lisp:
(defun our-remove-if (fn lst) (if (null lst) nil (if (funcall fn (car lst)) (our-remove-if fn (cdr lst)) (cons (car lst) (our-remove-if fn (cdr lst))))))
We can translate this almost word-for-word to Haskell:
if' a b c = if a then b else c ourRemoveIf fn lst = (if' (null lst) [] (if' (fn (head lst)) (ourRemoveIf fn (tail lst)) ((:) (head lst) (ourRemoveIf fn (tail lst)))))
The family resemblance is obvious, but it’s best to hide this beneath generous servings of Haskell syntax sugar:
ourRemoveIf _ [] = [] ourRemoveIf f (x:xs) | f x = ourRemoveIf f xs | otherwise = x : ourRemoveIf f xs
In this small example we see various sweeteners: the off-side rule; pattern matching; guards; infix and prefix notation; concise notation for lists.
There is substance behind the delicious style. Patterns are sophisticated
enough to be useful, yet elementary enough so compilers can detect overlapping
patterns or incomplete patterns in a function definition. This catches bugs
that would go unnoticed in a Lisp cond
.
With this in mind, we see the source of our interpreter is almost the same as
Graham’s, except it’s less cluttered and more robust. For example, for
the 7 primitives, thanks to pattern matching, the function f
reduces
duplicated code such as eq (car e)
and
detects errors when the wrong number of arguments are supplied.
By the way, as with Lisp, in reality we would never bother defining the above
function, because ourRemoveIf = filter . (not .)
.
Less is more
Haskell is really the Core language, coated in heavy layers of syntax sugar. The Core grammar only takes a handful of lines:
data Expr b = Var Id | Lit Literal | App (Expr b) (Arg b) | Lam b (Expr b) | Let (Bind b) (Expr b) | Case (Expr b) b Type [Alt b] | Cast (Expr b) Coercion | Tick (Tickish Id) (Expr b) | Type Type | Coercion Coercion deriving Data type Arg b = Expr b data Bind b = NonRec b (Expr b) | Rec [(b, (Expr b))]
Parallels with Lisp are obvious, for example, Lam
is lambda
, Case
is
cond
, and App
is the first cons cell in a Lisp list, There’s bookkeeping
for types, and source annotation (Tick
) for profilers and similar tools, but
otherwise Core and Lisp share the same minmalist design.
History versus myth
Time has given Lisp a legendary status which is perhaps only partly deserved. David Turner’s brief history of functional programming languages dispels some Lisp myths:
-
Lisp had assignments and goto before it had recursion, and started as a dialect of Fortran! It was only later that Lisp programmers investigated the benefits of pure functions.
-
Lisp was not based on lambda calculus, but rather Kleene’s work on recursive functions. At the time, McCarthy had heard of lambda calculus but had not yet studied it! It was only in 1975 that Scheme saw the light and gave us a Lisp based on lambda calculus.
-
Lisp’s M-language was first-order, that is, functions could not be passed around. However, you could pass around something like a string representation of a function (an S-expression). Though useful, free variables behave so oddly that McCarthy thought it was a bug: we get dynamic binding instead of lexical. (This reminds us meta-programming and higher-order programming are different.)
Lisp’s murky beginnings manifest as code smells in our implementation.
-
Why are
cond
andquote
singled out as being lazy (and thus not "functions" to use Graham’s terminology)? Because like all eagerly evaluated languages, Lisp must hang onto at least one non-strict function to support conditional branching and looping. -
The
label
function complicates our code. Would it be better as a special top-level construct? -
The
atom
primitive returns true for all atoms, but also a special case of a list: the empty list. -
We lack support for dotted pairs because we used lists. Lisp actually uses binary trees, despite its name.
Thanks to standing on Lisp’s shoulders, as well as theoretical advances, Haskell is built on a more solid foundation:
-
Purity and lambda calculus were baked into the language from the start.
-
Lazy evaluation largely obviates the need for macros.
-
The Hindley-Milner type system underpinning Haskell 98 lets us write code without a single type annotation. It feels like Lisp, yet an efficient type inference algorithm means the compiler rejects badly typed programs. Haskell has since gone beyond Hindley-Milner, but even so, type annotation is inconspicuous.
-
The Core language is built on System F, which is formalizes parametric polymorphism and also guarantees programs terminate.
-
Haskell is better connected with mathematics. Proofs are easier. See also the Curry-Howard correspondence.
-
Roughly speaking, Lisp reads
(min 1 x)
as(min (1 x))
, while Haskell reads it as((min 1) x)
. For function evaluation, Haskell’s parse tree is more troublesome because we must repeatedly traverse left from the root to find the next node to reduce, rather than simply take the left child of the root. However, it’s a net win because a curried function is a subtree. We have lambda calculus and combinatory logic to thank for left-associative function application. -
While it’s cool that a Lisp program is its own representation ("homoiconicity"), this blurring of the use-mention distinction trips up everyone from students (who have trouble with
quote
) and theorists (who have trouble formally reasoning about it). Haskell wisely chose a more explicit form of metaprogramming.