Syntactic Abstractions

2017-February-22

The previous post explained higher-order functions and the abstractions they enable us to build. The programming techniques we discussed there can be applied in any functional language. This post describes a kind of abstraction that can be built only in Lisp. I am referring to Lisp's ability to abstract over its own syntax.

If you have programmed in a language like C, Java or Python, you realize how "sacred" the idea of syntax is – those rigid, inviolable rules established by high-ranking language lawyers. But once in a while we do feel that if the language had such and such an operator or control construct, our life would've been easier. For instance, consider a Java programmer trying to iterate over a table in a relational database and do something with the data in each row:


String sql = "SELECT name, salary FROM employee WHERE salary > 1000";
Statement s = new Statement(sql);
ResultSet r = dbconnection.executeQuery(s);
while (r.next()) {
   String employeeName = r.getString("name");
   double employeeSalary =  r.getDouble("salary");
   doSomething(employeeName, employeeSalary);
}

After repeatedly typing in the same pattern of code many times over, our Java programmer starts to wish for a built-in language construct specially designed for iterating over database rows. This is the language extension he has in mind:


String sql = "SELECT name, salary FROM employee WHERE salary > 1000";
for_each_row (dbconn, sql, String employeeName = name,
              double employeeSalary = salary) {
  doSomething(employeeName, employeeSalary);
}

The for_each_row construct will enable him to program the database from a higher level, in a declarative style. He just specifies what data he wants to fetch, establish some local variable bindings for them and do his work with those values. The compiler recognizes for_each_row as a special construct and emits all the lower-level code required to access and bind the variables.

We all know this is just wishful thinking! Application programmers are not allowed to change the language just like that. They are expected to solve their problems while staying within the boundaries established by the language designers. Well, not so if you are programming in Lisp!

Lisp elevates the status of application developers to that of language designers. If you think that adding a new syntactic extension to the language will make your program cleaner, shorter and faster, you just go ahead and add it.

Expressions and the rules of evaluation

Before we delve into extending Lisp with new syntax, we should get a high-level overview of how Lisp programs are encoded and interpreted. Lisp programs consist of expressions of two types – atomic and compound. An atomic expression (or atoms) consists of a value that cannot be split any further. An integer literal like 23 is an example of an atom. The rules for evaluating an atom are,

  1. If an atom is a literal, like the number 23, just return the value as-is.
  2. If the atom is a symbol representing the name of a variable, fetch and return the value associated with that variable. (The variable name will be mapped to a value in an in-memory store, usually known as the environment).

Note: Atomic values are also known as scalars in other languages.

Compound expressions are formed by delimiting a list of expressions within parenthesis. They are also known as combinations and they denote function application. The following are all examples of combinations:


(+ 2 3)
(* 10 (+ 2 3))

These are the rules followed by a Lisp interpreter for evaluating a combination:

  1. Evaluate each expression in the combination
  2. Apply the function (i.e, the value of the left-most expression, known as the operator) to the other sub-expressions (arguments or operands).

Lisp also allow expressions to be quoted. This is done by prefixing the expression with the quote character (') or with a call to the quote operator. Quoted expressions are not evaluated by the interpreter, instead their literal representation is returned.

The following session at the Clojure REPL demonstrates all the evaluation rules we discussed so far:


user> 23 ; an atom
;;  23

;; a combination with + as operator and 2 and 3 as operands.
user> (+ 2 3)
;; 5

;; another combination with * as operator and 10 and
;; the value of the combination `(+ 2 3)` as operands.
user> (* 10 (+ 2 3))
;; 50

user> (def x 100)
user> x ; an atom that names a variable.
;; 100
user> 'x ; the same atom, quoted
;; x
user> '(+ 2 3) ; quoting turns-off evaluation.
;; (+ 2 3)
user> (quote (+ 2 3)) ; same as '(+ 2 3)
;; (+ 2 3)
user> (quote x) ; same as 'x
;; x

As we noted earlier, the call to quote behaves differently from a normal function call. It appears that quote gets the whole expression passed to it, unevaluated. This is because quote is an operator specially recognized by the interpreter/evaluator. Most Lisps have a small set of such operators with unique evaluation rules. These operators are known as special forms.

The evaluation rules for atoms, function calls and special forms sums up the behavior of a Lisp interpreter. It is this amazing simplicity in representation and evaluation that makes Lisp a language extensible to the core.

Note: Though we explained the evaluations rules in the context of an interpreter, they apply equally well for a compiler.

Macros

Now we have enough background to understand the syntax-level extension facility offered by Lisp. Let us begin with a very simple but realistic syntactic extension. Imagine you want to define an operator that evaluates its body only when some condition is false. In Clojure you can use the built-in if-not or when-not operators for this, but you feel that the code will be more readable if you can write something like – (unless this-is-true do-this). It is possible to define unless as a higher-order function as shown by the following program:


(defn unless
  [condition consequent]
  (when-not condition (consequent)))

;; Example usage:
(unless (< 2 1) #(println "ok"))
;;> ok
(unless (< 1 2) #(println "ok"))
;; nil
(unless (< 2 1) (fn [] (println "ok") 100))
;;> ok
;; 100

Note: In the code samples, ;;> denotes the result of a side-effect, like printing to the standard output.

The problem with this definition is that the users of unless have to wrap the consequent expression in a function literal. Otherwise it will be evaluated when unless is called, no matter what the condition is. This is because all the arguments are evaluated before the function call itself. In other words, the evaluation rules for function call is different from special forms. An argument passed to special forms are evaluated only when its value is really needed by the operator. The good news is that we can add our own special forms to extend the Lisp interpreter or compiler! These user-defined special forms are known as macros. A macro is introduced to the Clojure compiler with a defmacro definition. Let us rewrite unless as a macro:


(defmacro unless
  [condition consequent]
  `(when-not ~condition ~consequent))

(unless (< 2 1) (println "ok"))
;;> ok
(unless (< 1 2) (println "ok"))
;; nil

The unless macro behaves more like a built-in operator, we can pass a raw expressions in the consequent part. We are also able to avoid the runtime cost of creating and calling a function. Let us spend some more time understanding the special treatment given to a macro by the compiler.

A macro is essentially a function that is called by the compiler. Consider the expression (unless (< 2 1) (println "ok")). When the compiler detects that this is a call to a macro, it asks the Lisp interpreter to kick-in and evaluate the body of unless with the arguments (< 2 1) and (println "ok"), just like it would evaluate a function call. Note that the value returned by unless is a quasiquoted list (a list prefixed by the backtick character (`)). A quasiquoted expression is similar to a quoted expression, in that the evaluator is turned-off and the expression is returned literally. But a quasiquoted expression can contain "escaped" or unquoted sub-expressions. The evaluator will evaluate these unquoted sub-expressions and replace them with their values. (Clojure uses the tilde (~) character for unquoting expressions).

It will be easier to understand the difference between quote and quasiquote by playing around a bit in the REPL:


user> (def a 10)
user> (list a a)
(10 10)
;; the quote turns-off the evaluation of the
;; elements in the list.
user> '(a a)
;; (a a) 

;; A quasiquote without any escaped sub-expressions
;; has the same effect as a quote.
user> `(a a)
;; (a a)
user> `(~a a)
;; (10 a)
user> `(~a ~a)
;; (10 10)

So in our example, the evaluator replaces ~condition and ~consequent with the lists (< 2 1) and (println "ok") respectively. This results in the final expression (when-not (< 2 1) (println "ok")). The compiler then proceeds to replace the call to unless with this expression. This is as good as typing the when-not expression directly into the program. This phase of compilation when the macro is "called" to return some auto-generated code is known as "macro expansion". Macro expansion happens only once in the life-time of a macro call. The expanded code may be executed multiple times when the program runs, without any additional overhead.

Exercise 1: In Clojure, the built-in function macroexpand can be called to find out the expansion of a macro. Use this function to return the expansion of the call (unless (< 2 1) (println "ok")). Find out why the resulting expansion is different from the template code we provided in the body of unless. Also figure out the use of macroexpand-1 and macroexpand-all. These functions will come in handy for debugging complex macros.

Our current implementation of unless has a limitation – it can accept only a single expression in the consequent part. Let us fix this by taking advantage of a macro's ability to accept an arbitrary number of arguments. These arguments are all packaged into a list and passed to the macro. This list has to be introduced as a parameter by preceding it with an ampersand (&). Before changing unless, let us look at a simpler example. The following program defines a macro that can merge an arbitrary number of values into a single vector.


(defmacro into-vec
  [a & args]
  `[~a '~args])

(into-vec 1 2 3 4)
;; [1 (2 3 4)]

This first version of the into-vec macro does not do exactly what we want. We want the argument list to be "spliced" into the resulting expression. This can be achieved by using the unquote-splice (~@) operator:


(defmacro into-vec
  [a & args]
  `[~a ~@args])

(into-vec 1 2 3 4)
;; [1 2 3 4]

Now we know how to make unless accept more than one expression in the consequent part. Just define it to take an arbitrary number of arguments after condition and unquote-splice those into the body of when-not:


(defmacro unless
  [condition & consequent]
  `(when-not ~condition ~@consequent))

;; Example usage:
(unless (< 2 1)
  (println "hey")
  (println "there!")
  (+ 2 1))
;;> hey
;;> there!
;; 3

When to use macros

We can use both higher-order functions and macros to define custom control structures, but macros have some advantages here. First of all, macros can save a few keystrokes, because they can get rid of explicit function literals. Secondly, there may be some performance advantage, as macros avoid a function call at runtime by directly injecting the code into the call-site.

Some programs may want a piece of code, like a frequently performed expensive math calculation, to be highly optimized. What is the best way to optimize a computation? By not doing it! Well, to be fair, by not doing it at runtime. If we can pre-compute the result at compile-time, why not do that and insert the final result into the program? Macros can help with compile-time computations. In the following example, we define such a macro. It does some checks to see if it has all the information needed to perform the computation at compile-time itself. If that is possible, the computation is executed and the result is returned to the compiler. If not enough information is available to do the computation at compile-time, the macro will return the code that can do the computation later at runtime:


(defmacro fast-hypot
  [x y]
  (if (and (number? x) (number? y))
    (Math/hypot x y)
    `(Math/hypot ~x ~y)))

(macroexpand-1 '(fast-hypot 123.22 145.67))
;; 190.7954855335943
(macroexpand-1 '(fast-hypot a 145.67))
;; (java.lang.Math/hypot a 145.67)

Functions are the natural building blocks of Lisp, their implementation is highly optimized and they have first-class status in the language. Too many macro calls tend to bloat the final program generated by the compiler by having the same code copied to multiple locations. If a syntactic extension to the language makes it cleaner, faster and easier to maintain, go for macros. If you have to define a custom language to solve a particular problem, you may have to depend a lot on macros. In all other situations, stick to functions. So the guiding principal is – use functions whenever you can and use macros when you have to.

Macro caveats

Macros are vulnerable to certain types of bugs that do not usually occur with normal functions. This section throws light on some of those issues.

Variable capture

Variable capture occurs when a symbol in the expanded macro body ends up referring to a variable from another context. If the variable capture is unintentional it can lead to subtle bugs. In the next program, we define a macro that will capture a variable from the context it is called.


(def x 100)
(defmacro prnx
 []
 `(println ~'x))

(prnx)
;;> 100
(let [x 200] (prnx))
;;> 200

The macro prnx has a bug if the macro writer intended it to always print the value of the global variable x. This simple macro highlights one way a capture can occur – by means of free variables. A variable is free in an expression if that expression does not create a binding for it. The prnx macro do not bind the variable x in its body nor in its parameter list. This opens up x to obtain a value from the context in which prnx is called and may lead the macro to behave in unintended ways. If you want to avoid a variable from being captured, make sure it does not occur free in the macro body.

Let us try to write a macro that do not have any free variables and thus avoid variable capture. For this I decided to implement a slightly more complicated macro – a control structure that imitates the behavior of the for loop found in most imperative languages. Here is the first version of our for loop:


(defmacro for-loop
  [var-name start-from loop-until & body]
  `(let [~'end ~loop-until]
     (loop [~var-name ~start-from]
       (when (< ~var-name ~'end)
        (do ~@body
            (recur (inc ~var-name)))))))

The for-loop construct seems to work under all normal circumstances:


(for-loop x 0 3 (println x))
;;> 0
    1
    2

But when we use the symbol end for the loop variable, a subtle bug raises its ugly head to the surface:


(for-loop end 0 3 (println end))

A call to macroexpand-1 reveals why the macro is not working as expected:


(macroexpand-1 '(for-loop end 0 3 (println x)))
;; (clojure.core/let [end 3]
       (clojure.core/loop [end 0]
         (clojure.core/when
           (clojure.core/< end end)
             (do (println x)
                 (recur (clojure.core/inc end))))))

The problem is the hard-coded symbol end we used to name a local variable. The variable name passed to the macro by the user is shadowing this variable. This means that just avoiding free variables is not enough to get rid of variable capture. We also need to ensure that the local variable names bound in the macro body are unique across the system. The function gensym can help us here. It returns a new symbol that is guaranteed to be unique. Let us rewrite the for-loop macro using gensym:


(defmacro for-loop
  [var-name start-from loop-until & body]
  (let [end (gensym)]
    `(let [~end ~loop-until]
       (loop [~var-name ~start-from]
         (when (< ~var-name ~end)
	   (do ~@body
	   (recur (inc ~var-name))))))))

(for-loop x 0 3 (println x))
;;> 0
    1
    2
(for-loop end 0 3 (println end))
;;> 0
    1
    2

Note that the first let expression is not part of the code template returned by the macro. It is not quasiquoted. So it will be evaluated during compile-time, binding the variable end to a unique symbol value. This symbol is used in the code template to ensure that no name clashes occur. Now, having to write this extra code for generating local symbol names can be tedious if the macro has lots of them. So Clojure offers us a shortcut. You can suffix a variable name with the hash (#) character and the Clojure compiler will consistently replace that name with a unique symbol. This replacing will happen as long as the name occurs within a quasiquoted expression. This facility is demonstrated below:


user> (let [a# 1] a#)
;; 1
user> '(let [a# 1] a#)
;; (let [a# 1] a#)
user> `(let [a# 1] a#)
;; (clojure.core/let [a__2875__auto__ 1] a__2875__auto__)

Now we are ready to write the final, correct version of our for-loop macro:


(defmacro for-loop
  [var-name start-from loop-until & body]
  `(let [end# ~loop-until]
     (loop [~var-name ~start-from]
       (when (< ~var-name end#)
         (do ~@body
             (recur (inc ~var-name)))))))

Tidbit: Macros in Scheme do not have the variable capture problem because the macro system is "hygienic". The macro expander takes care of properly renaming variables locally bound by the macro body. If the macro refers to any free variable, the expander makes sure that the reference seen by the macro will always be the one when the transformer was specified.

Now you may wonder if there is a way to fix the broken prnx macro. We can take advantage of the Clojure namespace system to force prnx to refer to the global variable we intended. We just qualify the free variable with the namespace that it belongs to.


user> (def x 100)
user> (defmacro prnx
        []
        `(println ~user/x))

user> (prnx)
;; 100
user> (let [x 200] (prnx))
;; 100

Multiple evaluations

While reading the definition of the for-loop macro, some of you might have thought why I have introduced the extra variable end#. Why not directly check the value of the loop-until argument to determine when to exit the loop? Let us rewrite the macro without the extra local variable and examine the resulting behavior.


(defmacro for-loop
  [var-name start-from loop-until & body]
  `(loop [~var-name ~start-from]
     (when (< ~var-name ~loop-until)
       (do ~@body
            (recur (inc ~var-name))))))

The problem with this definition is that the expression passed to loop-until will be evaluated each time the loop is executed. This is evident from the following REPL session:


user> (for-loop x 0 (do (println "expensive computation....") 3)
         (println x))
;;> expensive computation....
0
expensive computation....
1
expensive computation....
2
expensive computation....

If there is no other reason, you should unquote and evaluate the arguments only once, bind the results to local variables and refer to those variables in the rest of the macro body. This was what the earlier definition of for-loop was doing and it did not suffer from this "multiple-evaluation" problem.

The order in which macro arguments are evaluated can also become an issue, especially if the argument expressions perform side-effects. You can avoid this problem by sticking to pure functional programming as much as possible. The macro expansions should also be purely functional. Expander code should depend on nothing but the expressions passed to it as arguments and should not perform any side-effects other than returning a value.

Conclusion

It is the unique nature by which Lisp programs are encoded and interpreted that makes it an extensible language. This amazing extensibility has enabled Lisp to be a great survivor. When new programming paradigms emerged, older languages died out. But Lisp simply adapted to the changing environment and moved on. It is this adaptability and flexibility that makes learning Lisp not only fun but also a safe investment.

Exercise 2: At the beginning of this post we talked about an extension to the Java language for making relational database access easier. Design and implement a similar extension as a Clojure macro.

Suggested reading

  1. On Lisp - everything you need to know about macros.
  2. The Art of Meta-Object Protocol - explains in great detail an object-oriented extension developed for Common Lisp, providing profound insights on the possibilities of syntactic abstractions.
  3. The Forth programming language also has an extensible compiler. Stating Forth is a great tutorial on the language (or on any language!).

Download

A solution to Exercise 2.