ezyang’s blog

the arc of software bends towards understanding

What Template Haskell gets wrong and Racket gets right

Why are macros in Haskell terrible, but macros in Racket great? There are certainly many small problems with GHC's Template Haskell support, but I would say that there is one fundamental design point which Racket got right and Haskell got wrong: Template Haskell does not sufficiently distinguish between compile-time and run-time phases. Confusion between these two phases leads to strange claims like “Template Haskell doesn’t work for cross-compilation” and stranger features like -fexternal-interpreter (whereby the cross-compilation problem is “solved” by shipping the macro code to the target platform to be executed).

The difference in design can be seen simply by comparing the macro systems of Haskell and Racket. This post assumes knowledge of either Template Haskell, or Racket, but not necessarily both.

Basic macros. To establish a basis of comparison, let’s compare how macros work in Template Haskell as opposed to Racket. In Template Haskell, the primitive mechanism for invoking a macro is a splice:

{-# LANGUAGE TemplateHaskell #-}
module A where
val = $( litE (intPrimL 2) )

Here, $( ... ) indicates the splice, which runs ... to compute an AST which is then spliced into the program being compiled. The syntax tree is constructed using library functions litE (literal expression) and intPrimL (integer primitive literal).

In Racket, the macros are introduced using transformer bindings, and invoked when the expander encounters a use of this binding:

#lang racket
(define-syntax macro (lambda (stx) (datum->syntax #'int 2)))
(define val macro)

Here, define-syntax defines a macro named macro, which takes in the syntax stx of its usage, and unconditionally returns a syntax object representing the literal two (constructed using datum->syntax, which converts Scheme data into ASTs which construct them).

Template Haskell macros are obviously less expressive than Racket's (an identifier cannot directly invoke a macro: splices are always syntactically obvious); conversely, it is easy to introduce a splice special form to Racket (hat tip to Sam Tobin-Hochstadt for this code—if you are not a Racketeer don’t worry too much about the specifics):

#lang racket
(define-syntax (splice stx)
    (syntax-case stx ()
        [(splice e) #'(let-syntax ([id (lambda _ e)]) (id))]))
(define val (splice (datum->syntax #'int 2)))

I will reuse splice in some further examples; it will be copy-pasted to keep the code self-contained but not necessary to reread.

Phases of macro helper functions. When writing large macros, it's frequently desirable to factor out some of the code in the macro to a helper function. We will now refactor our example to use an external function to compute the number two.

In Template Haskell, you are not allowed to define a function in a module and then immediately use it in a splice:

{-# LANGUAGE TemplateHaskell #-}
module A where
import Language.Haskell.TH
f x = x + 1
val = $( litE (intPrimL (f 1)) ) -- ERROR
-- A.hs:5:26:
--     GHC stage restriction:
--       ‘f’ is used in a top-level splice or annotation,
--       and must be imported, not defined locally
--     In the splice: $(litE (intPrimL (f 1)))
-- Failed, modules loaded: none.

However, if we place the definition of f in a module (say B), we can import and then use it in a splice:

{-# LANGUAGE TemplateHaskell #-}
module A where
import Language.Haskell.TH
import B (f)
val = $( litE (intPrimL (f 1)) ) -- OK

In Racket, it is possible to define a function in the same file you are going to use it in a macro. However, you must use the special-form define-for-syntax which puts the function into the correct phase for a macro to use it:

#lang racket
(define-syntax (splice stx)
    (syntax-case stx ()
        [(splice e) #'(let-syntax ([id (lambda _ e)]) (id))]))
(define-for-syntax (f x) (+ x 1))
(define val (splice (datum->syntax #'int (f 1))))

If we attempt to simply (define (f x) (+ x 1)), we get an error “f: unbound identifier in module”. The reason for this is Racket’s phase distinction. If we (define f ...), f is a run-time expression, and run-time expressions cannot be used at compile-time, which is when the macro executes. By using define-for-syntax, we place the expression at compile-time, so it can be used. (But similarly, f can now no longer be used at run-time. The only communication from compile-time to run-time is via the expansion of a macro into a syntax object.)

If we place f in an external module, we can also load it. However, we must once again indicate that we want to bring f into scope as a compile-time object:

(require (for-syntax f-module))

As opposed to the usual (require f-module).

Reify and struct type transform bindings. In Template Haskell, the reify function gives Template Haskell code access to information about defined data types:

{-# LANGUAGE TemplateHaskell #-}
module A where
import Language.Haskell.TH
data Single a = Single a
$(reify ''Single >>= runIO . print >> return [] )

This example code prints out information about Single at compile time. Compiling this module gives us the following information about List:

TyConI (DataD [] A.Single [PlainTV a_1627401583]
   [NormalC A.Single [(NotStrict,VarT a_1627401583)]] [])

reify is implemented by interleaving splices and typechecking: all top-level declarations prior to a top-level splice are fully typechecked prior to running the top-level splice.

In Racket, information about structures defined using the struct form can be passed to compile-time via a structure type transformer binding:

#lang racket
(require (for-syntax racket/struct-info))
(struct single (a))
(define-syntax (run-at-compile-time stx)
  (syntax-case stx () [
    (run-at-compile-time e)
      #'(let-syntax ([id (lambda _ (begin e #'(void)))]) (id))]))
(run-at-compile-time
  (print (extract-struct-info (syntax-local-value (syntax single)))))

Which outputs:

'(.#<syntax:3:8 struct:single> .#<syntax:3:8 single>
   .#<syntax:3:8 single?> (.#<syntax:3:8 single-a>) (#f) #t)

The code is a bit of a mouthful, but what is happening is that the struct macro defines single as a syntax transformer. A syntax transformer is always associated with a compile-time lambda, which extract-struct-info can interrogate to get information about the struct (although we have to faff about with syntax-local-value to get our hands on this lambda—single is unbound at compile-time!)

Discussion. Racket’s compile-time and run-time phases are an extremely important idea. They have a number of consequences:

  1. You don’t need to run your run-time code at compile-time, nor vice versa. Thus, cross-compilation is supported trivially because only your run-time code is ever cross-compiled.
  2. Your module imports are separated into run-time and compile-time imports. This means your compiler only needs to load the compile-time imports into memory to run them; as opposed to Template Haskell which loads all imports, run-time and compile-time, into GHC's address space in case they are invoked inside a splice.
  3. Information cannot flow from run-time to compile-time: thus any compile-time declarations (define-for-syntax) can easily be compiled prior to performing expanding simply by ignoring everything else in a file.

Racket was right, Haskell was wrong. Let’s stop blurring the distinction between compile-time and run-time, and get a macro system that works.

Postscript. Thanks to a tweet from Mike Sperber which got me thinking about the problem, and a fascinating breakfast discussion with Sam Tobin-Hochstadt. Also thanks to Alexis King for helping me debug my extract-struct-info code.

Further reading. To learn more about Racket's macro phases, one can consult the documentation Compile and Run-Time Phases and General Phase Levels. The phase system is also described in the paper Composable and Compileable Macros.

14 Responses to “What Template Haskell gets wrong and Racket gets right”

  1. Sean Westfall says:

    Great article! I don’t know much about Racket, but it might be worthwhile to investigate the relationship between GHC’s Template Haskell and C++ templates, which is where I believe Simon Peyton Jones and Tim Sheard got the original idea to include meta programming in Haskell (here’s the original paper: http://research.microsoft.com/en-us/um/people/simonpj/papers/meta-haskell/meta-haskell.pdf if interested). I believe C++ templates are compile time only, and that’s why haskell is also, but yes, TH would probably be more useful if they functioned more like a Lisp macro.

  2. Kosyrev Serge says:

    For further elaboration on the idea, one might look at how this aspect is specified in Common Lisp.

    As a tiny aside, one of the other things that Lisps get right is reification of their implementation, which essentially provides for an extensible compiler, in the end.

    In case of Common Lisp, the entire phasing aspect is reified into a very orthogonal construct, namely EVAL-WHEN: http://clhs.lisp.se/Body/s_eval_w.htm

    All top-level language constructs in Common Lisp macroexpand into a combination of several EVAL-WHEN forms — e.g., citting the above document:

     (defun bar (x) (defun foo () (+ x 3)))
    

    might expand into

     (defun bar (x) 
       (progn (eval-when (:compile-toplevel) 
                (compiler::notice-function-definition 'foo '(x)))
              (eval-when (:execute :load-toplevel)
                (setf (symbol-function 'foo) #'(lambda () (+ x 3))))))
    

    So, naturally, when one wants to call, within a macro definition, a function defined in the same file, one has to do:

    (eval-when (:compile-toplevel :load-toplevel :execute)
      (defun func (...) ...))
    
    (defmacro mac ()
      (func ...))
    

    ..and the compiler proceeds to compose the resultant nested EVAL-WHEN specifications — the external one, and the one coming from the DEFUN expansion. The result is that the (setf (symbol-function ‘foo) #'(lambda () (+ x 3))) subform gets evaluated at compile time.

    Naturally, absent that phase specification MAC will fail to compile.

    One thing that that deserves a separate mention is the very imperative nature of the suggested macroexpansion of DEFUN.

  3. Kosyrev Serge says:

    Even if it is of purely archaeologic interest — here is more about the semantics of the phase interaction between compile-time and run-time in Common Lisp:

    http://clhs.lisp.se/Body/03_bbc.htm
    http://clhs.lisp.se/Body/03_bca.htm

  4. Scott Moore says:

    Those wanting more details about the design of Racket’s phase-based macro system should check out Matthew Flatt’s paper “Composable and Compilable Macros: You want it when?” (available here: https://www.cs.utah.edu/plt/publications/macromod.pdf).

    Edward: Thanks! I’ve added this link to the main article text.

  5. Maxim Kulkin says:

    Would it be helpful if GHC could just compile functions defined before splice to be able to use it in splice? Like if you have some functions defined, then a splice, splice code is able to reference all functions defined/imported before it, then there is some code, then another splice. The second splice is able to use any normal code defined before plus code generated by first splice. And so on.

    I think it would solve all complications without need to explicitly mark functions for either compile or runtime. Also, GHC could (not sure if it does not) do dead code elimination (since compile time TH code is not used in runtime) so using compile and runtime code in the same module would not give you any penalty (like increased binary size).

  6. Maxim: That doesn’t address the confusion between compile-time dependencies (the code the macros use) and the run-time dependencies (what the resulting code uses.)

  7. Maxim Kulkin says:

    Why there should be a separation? I find it an advantage that you could reuse the same code in both compile and runtime.

    Actually, revisiting article’s text, I find some parts of it surprising. E.g. in “Phases of macro helper functions” you write about defining a function that could be used inside macro. But in Haskell the macro function (of “Q Decl” type) can actually use another functions to help in defining AST for macro expansion. There is no need to specially macro those functions. The only problem is, since Haskell is compiled language, you can not use functions defined in the same module in which macro expansion is happening (because this module wasn’t compiled yet and thus GHC can’t execute non-compiled code). The solution, as I previously noted, would be to introduce multi stage compilation. Right now there is only two stages – 1) expanding splices; 2) compiling unspiliced code. Instead if GHC could compile code before first splice, then expand splice and compile it, then compile next piece of normal code, next splice and so on.. Then the problem would be solved.

    Overall, I think that best solution would be to just being able to use code without any special markup/declaration syntax. If you look at Ruby, they use metaprogramming (which is how they call ways to programmatically generate code) interleaved with runtime code (obviously, because it is all runtime code).

  8. Leo White says:

    We had similar thoughts when thinking about what a macro system for OCaml should look like: http://www.lpw25.net/ocaml2015-abs1.pdf. We shamelessly borrowed Racket’s phase model and tried to adapt it to the OCaml module system.

  9. Paolo G. Giarrusso says:

    > I find it an advantage that you could reuse the same code in both compile and runtime.

    You can: just import the module in both phases. That can even ill share the compiled code if appropriate. However, the two instances get different runtime states, which is critical I. Racket and matters even in monadic Haskell.

    This is essential to support well deterministic separate compilation, see the cited paper; they describe several issues with not having a phase separation, as in previous Schemes and Lisps (probably including Common Lisp).

  10. Well, we should give Template Haskell a little credit: there are no top-level effects (besides type generativity, which coincides at all phases). I wouldn’t be surprised if, in the original design of Template Haskell, a phased system was considered, but decided to be unnecessary, because there is no runtime state to keep distinct. (But there are other reasons to be phased!)

  11. Kosyrev Serge says:

    Edward,

    to be fair, the /macroexpansion/ phase of “minimal compilation” in Common Lisp (the part that would roughly correspond to TH, as far as my understanding of TH goes) has no side effects, other than those directly caused by the macros themselves.

    The side-effectful /result/ of DEFUN macroexpansion is a mix of side-effectful forms to be evaluated at compile and run time — indeed.

  12. John Ericson says:

    And this is exactly what I was going for with http://mail.haskell.org/pipermail/ghc-devs/2016-January/011066.html :) It’s not to late to fix TH if we make a new one!

    In the thread and the trac issue you made, it was more or less settled to go for phases in cabal first: either reusing setup-depends or copying it for GHC plugins. But after that a fixed TH should be made too!

  13. AntC says:

    One of the uses I’ve seen for TH functions executing at compile time is to connect to a database; pull in table definitions; convert them to data decls. I don’t see how that function could get compiled ‘on the fly’ at compile-time(?)

    I guess that won’t work in a cross-compiling context — which is one of the issues raised.

    Really is the need to pre-compile and import template functions so awkward?

    I’m not clear, though, if you’re making a further point: GHC doesn’t make a distinction between imports-for-templating vs imports-for-executing. (Because it doesn’t know that some function is only called at compile-time vs. at run-time vs. both. I guess being called at both would be odd?)

    So are you saying: the object program includes a lot of dead code for template functions that’ll never be called at run-time? That sounds fixable: if, after template expansion, functions from a module are not invoked, and not exported, prune out the module. And/or we could look at the return type: if it’s in the Q monad, it can’t be called at run-time. OTOH does it really amount to much dead code? Is it going to impact performance?

    [Late posting because this article is mentioned from a ghc-devs thread https://mail.haskell.org/pipermail/ghc-devs/2017-April/014094.html
    But I don’t see that any of what Edward is saying has a bearing on performance of the compiler — which is David F’s claim. In fact if you’re going to compile template functions ‘on the fly’, that’ll make compile times worse(?) And you’ll be compiling them in each module that uses them, rather than compiling once for all(?) ]

  14. I feel that I have missed some context here. Let me say some true things instead.

    In your example with the database, the problem with mixing together compile-time and run-time code is that the resulting compiled code will *also* be linked against the code responsible for connecting to the database and using it. At the Cabal level (which is responsible for linking together the final program) there is no distinction, so it can’t know, “Oh, that code is dead at run time, I can eliminate it” (except perhaps if you are statically linking, in which the linker can recompute what code to drop.)

    You suggest pruning out “template” (compile-time) code in the compiler, but if I’m building a library of Template Haskell functions, which I intend to let another library make use of in their macros, I had better not prune them out, because someone is going to run them!

    But to the broader point, would this proposal help with the performance of GHC? I don’t really think so. When people complain about TH speed, they’re often actually complaining about TH causing their entire project to recompile even when it shouldn’t. That should be addressed through better dependency tracking (although, it is difficult to efficiently look up the “semantic” fingerprint of a function) and is orthogonal to the discussion here.

Leave a Comment