Providence Salumu edsko.net - Brief Intro to Quasi-Quotation (Show me the types already)

Brief Intro to Quasi-Quotation (Show me the types already)

Posted on May 9, 2013

This posts serves as a brief introduction to quasi-quotation in Haskell, because I couldn’t make much sense of the existing documentation, which gets bogged down in unnecessary details about writing parsers, the use of SYB, etc. Also, although quasi-quotation borrows syntax from Template Haskell, the TH expression [|e|] and the QQ [qq|e|] are false friends at best.

Recap: Template Haskell

Template Haskell is a library and language extension for writing Haskell meta programs: Haskell code that generates Haskell code (sometimes called macros in other language communities). The language extension allows us to quote Haskell expressions:

{-# LANGUAGE TemplateHaskell #-}

ex1 :: Q Exp
ex1 = [| \x -> x |]

ex2 :: Q Type
ex2 = [t| String -> String |]

The quote syntax [| someExpression |] is a convenient way to create quoted expressions; that is, values of type Q Exp ; likewise, [t| someType |] can be used to quote types. Q is the Template Haskell monad, which allows to create fresh variables, get location information, or even perform arbitrary IO; Exp and Type are types from the TH library that reify Haskell expressions and types. There’s nothing special about them; we could have written

ex2 = return $ AppT (AppT ArrowT ''String) (ConT ''String)

instead (the double tick indicates we want the name of the type, not the type itself).

We can use a quoted expression where Haskell expects an expression by splicing it; similarly for quoted types. For instance, we can write

ex3 :: $ex2
ex3 = $ex1

Quasi-Quotation

Quasi-quotation extends Template Haskell and makes it possible to write custom parsers. The most important data type is

data QuasiQuoter = QuasiQuoter {
    quoteExp  :: String -> Q Exp
  , quotePat  :: String -> Q Pat
  , quoteType :: String -> Q Type
  , quoteDec  :: String -> Q [Dec] 
  }

Here’s a trivial example:

qq1 :: QuasiQuoter
qq1 = QuasiQuoter {
          quoteExp = stringE
       }

But now here’s the confusing part: consider the following example

{-# LANGUAGE QuasiQuotes #-}

ex4 :: String
ex4 = [qq1|Hello|]

This is a splice, not a quote! The appropriate parser in the quasi quoter (depending on context) is used to convert the string to a quoted expression, and is then spliced in as an actual Haskell expression; in fact, this example is equivalent to

ex4' :: String
ex4' = $(quoteExp qq1 "Hello")

Really the only difference is that the syntax is somewhat more convenient, that it automatically picks the right parser for the context (type vs expression, etc.); moreover, quasi-quotes can be used in patterns, as we shall see below.

Meta-Variables and Anti-Quotation

First two more Template Haskell examples:

ex7 :: Lift a => a -> Q Exp
ex7 x = [| x |]

ex8 :: Q Exp -> Q Exp
ex8 x = [| $x |]

The first example uses simple type class defined in the TH libraries:

class Lift t where
  lift :: t -> Q Exp

The second example shows that we can splice inside quotes; actually, ex8 is an identify function (quoting and splicing are inverses). Unless we modify our quasi-quoter, however, the following two functions probably don’t have the intended effect (whatever the intended effect was):

ex7' :: a -> String
ex7' x = [qq1| x |]

ex8' :: a -> String
ex8' x = [qq1| $x |]

Both of these functions ignore their argument; the first evaluates to the string "x" and the second evaluates to the string "$x". If we want to support meta-variables we need to modify the parsers for our quasi-quoter. The convention is that parsers in quasi-quoters recognize $x as referring to a meta-variable x. We can define a quasi-quoter that only recognizes these as

qq2 :: QuasiQuoter
qq2 = QuasiQuoter {
          quoteExp = \('$' : n) -> varE (mkName n)
        }

and then define

ex9 :: a -> a
ex9 x = [qq2|$x|]

(But note the difference in type between ex8 and ex9.) In fact, if we extend our quasi-quoter with a parser for patterns too:

qq2 :: QuasiQuoter
qq2 = QuasiQuoter {
          quoteExp = \('$' : n) -> varE (mkName n)
        , quotePat = \('$' : n) -> varP (mkName n)
        }

then we can also use a quasi-quote in a pattern position (something that TH does not support):

ex9' :: a -> a
ex9' [qq2|$x|] = [qq2|$x|]

Conclusions

If you are already familiar with Template Haskell then quasi-quotation isn’t much of an extension, except that the resemblance in syntax is confusing and misleading. The only thing I haven’t covered in this short post are dataToExpQ and dataToPatQ, which are basically generic versions of TH’s Lift class, with support for anti-quotation. See Section 3.2 of the original paper for details.

Providence Salumu