I’ve been writing a lot of Janet lately, and I’ve been especially enjoying my time with the macro system.

Janet macros are Common Lisp-flavored unhygienic gensym-style macros. They are extremely powerful, and very easy to write, but they can be pretty tricky to get right. It’s easy to make mistakes that lead to unwanted variable capture, or to write macros that only work if they’re expanded in particular contexts, and it can be pretty difficult to detect these problems ahead of time.

So people have spent a lot of time thinking about ways to write macros more safely – sometimes at the cost of expressiveness or simplicity – and almost all recent languages use some sort of hygienic macro system that defaults to doing the right thing.

But as far as I know, no one has approached macro systems from the other direction. No one looked at Common Lisp’s macros and said “What if these macros aren’t dangerous enough? What if we could make them even harder to write correctly, in order to marginally increase their power and expressiveness?”

So welcome to my blog post.

I want to show you an idea for a new kind of macro. A macro that can not only rewrite itself, but actually rewrite any form in your entire program.

I think that “what, no, why on earth” is an entirely reasonable response to that statement, so let’s take a look at a motivating example together.

Lots of languages have something like defer that will run an expression at the end of a block, whether or not the rest of the code raises an exception. defer is just like wrapping the rest of the function in a try-finally block, except that, well, you don’t actually have to do any wrapping. Which means no indentation increase, and no extra nested parentheses.

Here’s an example of what defer might look in Janet:

(do
  (def f (file/open "foo.txt"))
  (defer (file/close f))
  (def contents (file/read f))
  (do-something-dangerous-with contents))

Now, we can’t implement defer as a traditional macro, because a traditional macro can only rewrite itself. But what we really want to do is rewrite the parent form that the defer appears in, to wrap its siblings in a finally expression:

(do
  (def f (file/open "foo.txt"))
  (finally
    (do
      (def contents (file/read f))
      (do-something-dangerous-with contents))
    (file/close f)))

So generalized macros let us write exactly this.1

I want to start at the punchline and work backwards, because my favorite part is how simple it is to write this. So although I don’t actually expect this to make any sense yet, let’s go ahead and look at the implementation of this defer macro:

(defmacro defer [] [expr]
  (macro lefts rights
    ~(,;lefts (finally (do ,;rights) ,expr))))

Pretty tame, right?

So in order to do understand how this works, we’ll have to change three things about macros:

  1. Macros no longer have to appear at the head of the form; they can appear anywhere within a form.
  2. Macros now have two argument lists: the forms “to the left” of the macro, and the forms “to the right” of the macro.
  3. Macros can either return new abstract syntax trees – like a traditional macro – or they can return new, anonymous macros as first-class values.

Let’s go through these ideas one at a time in slightly more detail, and then we’ll circle back to the definition of defer.

Macros can appear anywhere

Scheme already has something called “identifier macros,” which can appear anywhere within a form. You can use them to say that foo is a macro, and it can appear in any expression context, and then make (+ 1 foo) expand to something like (+ 1 (some complicated expression)).

But identifier macros can still only rewrite themselves. In order to do anything interesting with this, we need to add…

Macros can see forms “to the left” and “to the right”

On the face of it this might sound like I’m trying to introduce “infix macros,” so that you could write something like (1 + 2) and rewrite that to the traditional (+ 1 2) syntax. And, to be clear, that is a thing you can do:

(defmacro + [left] [right]
  [+ left right])

I think that infix macros could be very useful – we’ll talk more about that in a bit – even if infix math is not particularly compelling to someone practiced in the prefixual arts.

But the real reason to support “infix” macros is for cases like defer, where the (defer ...) expression occurs in the middle of a form, and acts as sort of an “infix” expansion point. But in order for that to work, we need to add…

First-class macros

I think this is the trickiest part to wrap your head around, but it’s the most important. This is the trick that allows macros to rewrite not only themselves, but also the forms around themselves – their parents, their grandparents, their… cousins? I guess? Any other form in your program, actually.

So the idea is that we can create first-class anonymous macros, and return them from our macro implementations. And then those macros will get expanded in the context of the parent form that they now appear in.

This is a lot like returning an anonymous function, except that functions are perfectly reasonable values to put in your abstract syntax trees… so it’s like returning a special function, a function with a little tag attached that says “hey, I’m not a real runtime value, I’m a macro, so you should call me before you finish macro expansion.”

And just to be super explicit: this is different from a macro returning a syntax tree that contains another macro invocation. You can already write “recursive macros,” or macros that return invocations of other macros. But by creating actual new first-class macros at expansion time, you can close over macro arguments and reference them during the next phase of expansion.

So with these changes in mind, let’s come back to the implementation of defer:

(defmacro defer [] [expr]
  (macro lefts rights
    ~(,;lefts (finally (do ,;rights) ,expr))))

Our defer macro takes two binding forms: [] and [expr]. So it expects no arguments to the left – the word defer has to appear at the beginning of its form – and it expects exactly one argument to its right. In other words, it looks like a normal, traditional prefix macro of one argument.

But then it returns an anonymous macro that closes over its expr argument. So if we just look at one step of the expansion, we’ll see an abstract syntax tree that looks like this:

(do
  (def f (file/open "foo.txt"))
  <macro>
  (def contents (file/read f))
  (do-something-dangerous-with contents))

But macro expansion isn’t over. After expanding the (defer ...) form, the macro expander will notice that it expanded to another macro, so it will expand that. Which winds up invoking our anonymous macro, passing it ['do '(def f ...)] as its “left” arguments and ['(def contents ...) '(do-something...)] as its “right” arguments.

And then that will return a replacement for the entire (do ...) form, giving us our final result:

(do
  (def f (file/open "foo.txt"))
  (finally
    (do
      (def contents (file/read f))
      (do-something-dangerous-with contents))
    (file/close f)))

Neat, right?

This type of macro gives us a lot more freedom to decide how we want our code to look. I’m honestly not really sure how much more freedom, because I haven’t spent very much time with the idea yet. But I’ve been thinking about it for a while, and I’ve come up with a few examples of things that we can do with this – some much dumber than others.

Let’s take a look at a few of them.

Nest less

I think that reducing the number of nested parentheses and general indentation might be the most compelling use case for this sort of macro. I mean, really this is all defer does: it lets you write finally with a little less nesting, and with the expressions in a slightly different order.

I spend most of my programming time writing OCaml. OCaml doesn’t have “block scope” or “function scope” like most languages – it has expression scope. You introduce new “variables” (they can’t actually vary; all OCaml bindings are “const") using let ... in, and the binding only exists on the right-hand side of that particular expression.

If you think about the nesting of the OCaml abstract syntax tree, it looks something like this:

(let x = 10 in 
  (let y = 20 in
    (x + y)))

But of course you don’t write OCaml like that. For one thing, the parentheses are redundant:

let x = 10 in 
  let y = 20 in
    x + y

For another thing, this triangular indentation is really annoying. So you actually write it like this:

let x = 10 in 
let y = 20 in
x + y

The parse tree for that expression is still nested, but it doesn’t look nested – you always format your code linearly.

So lisps also have let, but lisps don’t have the luxury of leaving off the parentheses, so we’re back to the first example:

(let [x 10]
  (let [y 20]
    (+ x y)))

And if we tried to write that without indentation, then…

(let [x 10]
(let [y 20]
(+ x y)))

Immediate aneurysm.

Fortunately, every lisp dialect that I know of mitigates this problem substantially by allowing let to introduce multiple bindings in a single form:

(let [x 10
      y 20]
  (+ x y))

Which means that we only have to increase the nesting by one level in the very common case that we have a series of let expressions. But by using generalized macros instead, we can write a version of let that doesn’t increase indentation at all. I’ll call it def:

(defmacro def [] [name value]
  (macro lefts rights
    ~(,;lefts (let [,name ,value] ,;rights))))

def lets us write code like this:

(def x 10)
(def y 20)
(+ x y)

Which gets transformed into code like this:

(let [x 10]
  (let [y 20]
    (+ x y)))

Of course Janet – and most lisps – have a “linear assignment” form like this built into the language. In Janet it’s called – coincidentally enoughdef.

In fact in Janet, def is actually the primitive way to create new bindings, and let is a macro that just desugars to do + def, which is very reasonable and pragmatic, but feels weird to me.

It feels weird to me because, in my mind, let should be syntax sugar for fn – Janet’s word for lambda. Because, after all, these two expressions are equivalent:2

(let [x 10] (+ x 1))

((fn [x] (+ x 1)) 10)

let allows us to write the expression in a much more natural order, but we can introduce new bindings without any lets at all.

This might sound like weird mathematical lambda calculus trivia, but it’s not: it’s important to understand introducing new variables as a special-case of function application, even if this particular function application happens to be trivial.

Because we can apply the same technique that we just used – rewriting def to let, and rewriting let to fn – to do something much more interesting.

Generalized function application

So Haskell has something called do notation. You’ve probably seen something like this before:

addAll :: [Int] -> [Int] -> [Int]
addAll xs ys = do
  x <- xs
  y <- ys
  return (x + y)
ghci> addAll [1, 2] [10, 20]
[11,21,12,22]

This is equivalent to the following Janet code:

(defn add-all [xs ys]
  (mapcat (fn [x]
    (mapcat (fn [y]
      [(+ x y)])
      ys))
    xs))

But I think the Haskell code is easier to read. Partly that’s because the argument order to Janet’s mapcat function makes the values we’re traversing appear in reverse order in our source code, and we could fix this by redefining mapcat with a argument different order:

(defn add-all [xs ys]
  (mapcat xs (fn [x]
    (mapcat ys (fn [y]
      [(+ x y)])))))

This reminds me of the transformation we did when we changed ((fn [x] (+ x 1)) 10) into (let [x 10] (+ x 1)). So what if we take it one step further, and do the same thing we did to get def?

(defn add-all [xs ys]
  (as x mapcat xs)
  (as y mapcat ys)
  [(+ x y)])

It’s not quite as concise as Haskell’s do notation: Haskell is able to use the type of the expression to determine what <- means, so there’s no need to specify the mapcat bit: it’s implied from the fact that we gave it a list.

Janet doesn’t have an analog for type classes, so we have to be a little more explicit, but this means that we can do more than just “bind” with the as macro. We can also map:

(defn add-all [xs ys]
  (as x mapcat xs)
  (as y map ys)
  (+ x y))

Implementing as is just as easy as implementing def:

(defmacro as [] [name f arg]
  (macro lefts rights
    ~(,;lefts (,f (fn [,name] ,;rights) ,arg))))

If you haven’t programmed in a language like Haskell, this particular syntax sugar might seem a little odd at first. But a specialized notation for generalized function application is extremely useful – we have it in OCaml too, through a syntax extension called ppx_let:

let%bind x = xs in
let%bind y = ys in
return (x + y)

I think OCaml’s notation is actually more clear than Haskell’s – it highlights the symmetry between “ordinary” let bindings and “fancy” let bindings like these. And because it can do more than just bind, we can also avoid the explicit return in OCaml:

let%bind x = xs in
let%map y = ys in
x + y

map and bind aren’t the only functions of this variety, either. Although monads are ubiquitous in OCaml, I spend a lot of my time working with arrows as well. And arrows have yet another notation: let%sub and let%arr.

All of these are generalizations of regular function application. Without worrying about what any of this means, just look at how similar the shape of these different type signatures are:

val (@@) : 'a   -> ('a   -> 'b)   -> 'b
val map  : 'a f -> ('a   -> 'b)   -> 'b f
val bind : 'a f -> ('a   -> 'b f) -> 'b f
val sub  : 'a s -> ('a r -> 'b s) -> 'b s
val arr  : 'a r -> ('a   -> 'b)   -> 'b s

Okay, I know; this isn’t supposed to be a blog post about monads or arrows. Let’s get back to macros.

Infix operators

So Janet has some very useful “threading” macros that allow you to write code in a more “linear” fashion than you could without them. They’re useful when you’re performing a series of transformations to a value:

(filter |(string/has-prefix? "a" $)
  (map string/ascii-lower
    (map |($ :name) 
      people)))

With the power of threading macros, you could write that like this instead:

(->> people
  (map |($ :name))
  (map string/ascii-lower)
  (filter |(string/has-prefix? "a" $)))

This is a lot like “method chaining” in other languages:

people
.map(person => person.name)
.map(name => name.toLowerCase())
.filter(name => name.startsWith("a"))

It’s easier for me to read the linear notation that uses the threading macro. But it’s not actually any easier to write it.

I like that method chaining allows me to write the code in the order of the operations: “Start with people, get the name, lowercase it, filter it to names that start with ‘a.'”

When writing the threading macro, though, the way you type this is “start with people, okay wait, go back, surround it in parentheses, add a ->> at the beginning, now move the cursor to the end of the form, and then get the name…”

I don’t like that. And I know that there are fancy editors that allow you to easily wrap expressions in threading macros or any other without repositioning the cursor, but I’d rather use a syntax that doesn’t require a structural editor to work with comfortably.

So here’s another way to write this:

(people
@ (map |($ :name))
@ (map string/ascii-lower)
@ (filter |(string/has-prefix? "a" name)))

This uses @ as an infix function application macro. I prefer | myself, and that’s the notation that I chose for Bauble, but | is how you create short anonymous functions in Janet, so I don’t want to step on that.

The main reason I prefer this notation is that it’s easier for me to type. I don’t know that it’s any easier to read than ->, but it allows me to write code in the order that I think it, and I like being able to choose a syntax that maps neatly onto my brain.

Another infix macro that I like is .. . is a convenient macro for looking up a keyword in a struct or table, so that you can write struct.key instead of (get struct :key).

In Janet struct.key parses as a single symbol, so we can’t actually implement this as a generalized macro without a separate preprocessing step to split it into three symbols. But we can use it as struct . key, which parses as three separate symbols:

(defmacro . lefts [key & rights]
  ~(,;(drop-last lefts)
    (get ,(last lefts) ,(keyword key))
    ,;rights))

Which we can then use like this:

(print foo . bar)
(print (get foo :bar))

This is very goofy looking, but you could imagine a language where . always parsed as its own symbol, so that we could just write foo.bar and have that expand to (get foo :bar) automatically.

Another infix macro that I think could be interesting is :, to create a pair.

Janet already uses : as a leader character for declaring keywords, so this won’t work in Janet. But you could imagine, again, a different language where : is used as a short way to create a pair of two elements. So:

foo:bar

Would become:

(foo bar)

This might be useful in languages that use wrapped lets, where you have to write:

(let ((x 10)
      (y 20))
  (+ x y))

Instead, you could write that as:

(let (x:10 y:20)
  (+ x y))

But have it parse in exactly the same way.

You could imagine it in cond as well:

(cond
  (> x 0): "positive"
  (< x 0): "negative"
  (= x 0): "zero"
  true: "nan")

Of course Janet doesn’t require wrapping each entry in a cond expression in parentheses, so this isn’t as compelling in Janet.

For a slight variation on this, imagine a macro called ::. It’s just like : – it creates a pair – but the pair appears in reverse order from how you write it. We’re well off the Janet path now, but we could use this as a concise notation for adding type annotations without an explosion of parentheses.

Let’s say we have a – function? macro? – something called Int that provides a type annotation to our compiler. We’d normally write the type of an expression like this:

(def x (Int (compute-thing)))

But look all those close parens! I don’t want to balance those. So instead, we could write:

(def x (compute-thing) :: Int)

Which is equivalent to the less intuitive (to me):

(def x Int:(compute-thing))

:: doesn’t mean “type annotation,” though, it just means “wrap in parentheses.” We could use it to do dumber things:

"hello" :: print

Which would expand, of course, to (print "hello"). But… I don’t know why you would want to do that.

Comment

Something that I occasionally wish for is a (comment ...) macro that lets me ignore code.

You can’t actually write such a macro in Janet. Janet has a macro called comment in the standard library, but comment always expands to nil, and nil is not nothing. This means there are lots of places you can’t use (comment ...):

(defn foo [a (comment this is a comment)]
  (print a))

If you tried to compile that, you’d get an error:

compile error: unexpected type in destruction, got nil

Because after macro expansion, the compiler actually sees:

(defn foo [a nil]
  (print a))

Which is not valid.

With generalized macros, though, you can write a comment that actually disappears:

(defmacro comment [] [&]
  (macro lefts rights [;lefts ;rights]))

(defn foo [a (comment this is a comment)]
  (print a))

After expansion, that will just be:

(defn foo [a]
  (print a))

Like it never happened.

if/else

One thing that sometimes trips me up when I’m writing Janet is if.

if takes three forms: a boolean expression, an expression to evaluate if it’s truthy, and an expression to evaluate if it’s falsy. Which is nice and concise, but it’s different enough from other languages that I use – languages with explicit elses – that sometimes I’ll write code like this by mistake:

(if should-do-something-important
  (print "okay, performing important work:")
  (perform-important-work))

That actually doesn’t perform important work – (perform-important-work) is the “else” section of that conditional. In order to do more than one thing in the “then” branch, we have to wrap all of the statements in do.

And of course Janet has a when macro that does exactly what I want:

(when should-do-something-important
  (print "okay, performing important work:")
  (perform-important-work))

Which doesn’t have an else branch, and usually when I’m writing an if without an else I should just use when in the first place.

But.

Generalized macros actually let us write if with an explicit else. I’m not saying this is a good idea, but they let us write something like:

(if (empty? name)
  (print "you must provide a valid name"))
(else
  (print "okay i think it checks out"))

This example is a little weird because, in order for this to work nicely, we’ll have to rename the built-in if. I’ll call the ternary version if-then-else for this example, and say that if now means the same thing as Janet’s when.

(defmacro else [] [else-exprs]
  (macro lefts rights
    (match (last lefts)
      ['if & then-exprs]
        ~(,;(drop-last lefts)
          (if-then-else (do ,;then-exprs) (do ,;else-exprs))
          ,;rights)
      (error "else must come immediately after if"))))

This is interesting because the else macro actually rewrites the form before itself, changing the if to an if-then-else and then fussing with its arguments.

Weirder, more exotic things

I could keep going, but, as you have probably noticed, this is already a very long blog post. There’s a lot more that you can do with generalized macros – some of it useful, some of it unhinged, and we don’t have time to talk about all of it.

So far we’ve only seen macros that rewrite their parents or immediate siblings, but you can write macros that return macros that return macros, and use them to rewrite arbitrary forms anywhere in your program. You could write a macro that rewrites “the nearest enclosing function definition,” recursively accumulating first-class macros until finally expanding all of them.

You can write actual left- and right-associative infix operators, and I think that if you tried hard enough, you could even use dynamic variables and controlled macro expansion to implement infix operator precedence (although I don’t think you should).

You could implement (a weaker version of) Janet’s splice built-in as a generalized macro. You could implement “identifier macros” that look around themselves and expand to something different when they appear as the first argument to a (set ...) form. You could, you could…

You could do a lot of things, but I’m going to have to leave these as exercises to the reader, because it’s time to switch gears and talk about why you shouldn’t do this.

Problem one: the repl

The main reason that this seems like a bad idea is that macros like this don’t work at the top level.

If you’re just using the repl, and you type (defer (file/close f)), what happens? One of the arguments to that macro is “everything to the right.” But there isn’t anything to the right! At least, not yet. And it won’t be able to supply everything to the right until you stop typing altogether.

This might not seem like a big deal for defer – just don’t use defer at the repl – but it is a big deal for, say, def. And I don’t know an elegant way to solve this problem: in the general case, macros could look arbitrarily far ahead, so we’d have to wait until we closed the repl session to be able to expand them. And that’s kinda gross.

Problem two: generalized macros don’t always compose

All of the examples that we’ve seen so far play nicely together, but it’s possible to write generalized macros that don’t compose with one another.

The problem is that macro behavior can depend on expansion order. Regular macros always get a chance to run before their arguments get expanded, which is very convenient. Generalized macros don’t have that luxury – because macros can see the forms around them, the order that you expand those forms matters.

In my implementation I chose to expand macros in a depth-first, left-to-right order. So macros always see the arguments “to the left” of themselves fully expanded, and the arguments “to the right” completely unexpanded.

And this can be problematic. For example, let’s say we make an infix alias for set, called :=:

(var x 0)
(x := 1)

Which expands to:

(var x 0)
(set x 1)

This is a trivial generalized macro to write.

Now let’s say we have another macro, which looks at the form to its left to see if it immediately follows set. When it does, it rewrites that set to something else. We could use this to implement some kind of custom associative data structure:

(defmacro at [] [dict key]
  (macro lefts rights
    (if (= lefts ['set])
      ~(assign ,dict ,key ,;rights)
      ~(,;lefts (lookup ,dict ,key) ,;rights))))

So that macro lets us write:

(set (at dict key) 10)

And have that expand to:

(assign dict key 10)

Meanwhile, if we write (print (at dict key)), that will expand to (print (lookup dict key)).

Each of these generalized macros make sense on their own. But if we try to use them together, they just don’t work:

((at dict key) := 1)

Because (at dict key) expands first. It looks at the forms to its left, sees that there aren’t any, so after one step of expansion we have:

((lookup dict key) := 1)

Then we expand :=, and finish with:

(set (lookup dict key) 1)

Which of course was not what we wanted.

I think that using generalized macros safely requires really understanding the effect that they have on the syntax tree of your program. They’re more like ->> and friends – explicit syntax re-arrangers – than they are like other kinds of macros.

Problem three: you have created in your code a work of madness that no other human being can possibly hope to understand

ugh not again

Prior art

I feel like this approach is so simple that it must have been done before, but I can’t find any references to it. That said, I have no idea how to search for it effectively! So if you’ve seen this technique before, or if you’ve heard of it being used in the past, I’d love to hear about it.

Proof of concept

I implemented this macro system in Janet, in order to play around with it and test out my macro implementations.

It was pretty easy to write! It really is a very modest generalization of a traditional macro system. I didn’t actually write a custom module loader that would let you use this as your default macro system in Janet code, but I wrote (the equivalent of) macex, and adding the custom module loader would be pretty easy if you wanted to use it “for real.”

You can look at the code here: https://github.com/ianthehenry/macaroni

Or take a peek at some of the tests, to see the examples in this post in action, as well as some weirder things that didn’t make the cut.


  1. Of course we could teach do to scan through all of its arguments and look for defers, and implement this that way, but then this would only work in do expressions. What if we want to do this inside a (fn [] ...) block? Or an if? Or a while? By making defer itself do the transformation, we can use it anywhere – and make it easy to add new macros that behave like defer, without having to teach do about them. ↩︎

  2. Back in the Old Days, JavaScript only had function-scoped variables, so the only way to create new bindings in JavaScript code was to create and invoke an anonymous function like this. The pattern was so common that we called them “immediately invoked function expressions,” and it was a real thing that you had to do in order to, for example, close over distinct values in a loop. ↩︎