Quasi quoting

Simon Peyton-Jones simonpj at microsoft.com
Sat Feb 6 13:12:57 EST 2010


Max, Dominic

Thank you for the thinking you've done on this.

It's true that a quasi-quote really is a splice -- that's why there's a "$" in the current syntax.  But nevertheless quasiquotes and TH are quite different in other ways, and I don't think it'd be easy to merge them.

* TH quotes are parsed, renamed (scope analysis), and typechecked, all by the main GHC parser, renamer, typechecker.  I don't want to use some other parser, reanmer or typechecker for that or we'll get into compatibility issues quite apart from duplication.

* TH splices $e work for arbitrary expressions e.  The expression e must be typechecked before being run. So splices must be run by the type checker.

* In contrast, quasi-quotes are effectively always well-typed, since they run the code (parser s), where
'parser' is the user-supplied parser and 's' is a string.  That makes it easy to run quasi-quotes before typechecking.

* Quasi-quotes can yield patterns, and so they must be run by the renamer. That way a quasiquote that expands to a pattern can bind variables, and all that binding structure is sorted out by the renamer.  So a quasiquote not only *can* be run in the ranemer, it *must*.

* The user interface of this stuff is important.  People who write the functions that are called in splices might put up with some clumsiness, but the *invoker* of the splice (a client of the library, say) doesn't want too much clutter.

So unless I'm missing something I'm not that keen.  The current setup seems quite good.

Simon

| -----Original Message-----
| From: omega.theta at gmail.com [mailto:omega.theta at gmail.com] On Behalf Of Max
| Bolingbroke
| Sent: 01 February 2010 14:25
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users at haskell.org; Kathleen Fisher;
| mainland at eecs.harvard.edu
| Subject: Re: Quasi quoting
| 
| Dominic Orchard and I have come up with a rather radical proposal for
| a redesign of the syntax. There are two principal options:
| 
| OPTION 1 (preferred)
| ===============
| 
| Advantages:
| 1) QuasiQuotes are revealed as they really are - as splices. In my
| opinion this is much less confusing, because a "quasiquote" is really
| about generating *code*, like a $(), not about generating a *data
| structure* like the existing [|e|], [t|t|] and [d|d|].
| 2) Unifies Template Haskell and QQ into one construct
| 3) QQ looks like "semantic brackets"
| 4) No list comprehension ambiguity
| 
| Disadvantages:
| 1) Small syntax changes to QQ and TH. Increased verbosity in some common
| cases.
| 
| Start with GHC Haskell. Remove [|e|], [t|t|], [d|d|] and [e|..|] syntax.
| 
| Add this new syntax:
| 
| Syntax: [|...|]
| Type: String
| Translation: "..." (i.e. this is an alternative string literal syntax)
| 
| Now change the semantics of splice, $(e), like so:
|  1) If e :: Q Exp and we are in an Exp context in the code, run the
| computation and splice the resulting code in
|  2) (.. similarly if e :: Q Typ in a Typ context or Q [Decl] in a Decl
| context. NB: this is what we had to do for TH before anyway)
|  3) If e :: QuasiQuote then select the appropriate field from the
| evaluated "e" based on the context, run the Q computation it contains,
| and splice the resulting code in
| 
| Where:
| 
| data QuasiQuote = QuasiQuote {
|    quoteExp :: Q Exp
|    quotePat :: Q Pat
|  }
| 
| Now provide exports from Language.Haskell.TH:
| 
| e :: String -> Exp
| t :: String -> Type
| d :: String -> [Decl]
| 
| Which parse the provided string as Haskell into the usual data
| structure. Uses of Template Haskell quotes must be rewritten:
| 
| [|..|] ==> e [|..|]
| 
| [t|..|] ==> t [|...|]
| 
| [d|...|] ==> d [|...|]
| 
| QuasiQuotes now look like:
| 
| [foo|...|] ==> $(foo [|...|])
| 
| Where foo :: String -> QuasiQuote and defines the language you want to parse.
| 
| 
| OPTION 2 (not so good)
| =================
| 
| Advantages:
| 1) Normal Template Haskell use looks almost the same as before
| 2) QuasiQuotes are revealed as they really are - as splices
| 3) Unifies [t| ... |], [d| ... |] and QQ into one construct
| 
| Disadvantages compared to option 1:
| 1) [| |] is still a special case
| 3) QQ doesn't look like semantic brackets
| 4) List comprehension ambiguity remains
| 
| As GHC Haskell, but with a new interpretation for the QuasiQuote syntax.
| Syntax: [e1| ... |]
| Types: if e1 :: String -> a, [e1| ... |] :: a
| Translation: e1 "..."
| 
| Preserved TH syntax: [| ... |]
| Type: [| ... |] :: Exp
| Translation: ADT representing "..." parsed as a Haskell program
| 
| Adopt the new semantics of $() exactly as in option 1.
| 
| Now any existing uses of QQ should be rewritten as:
| 
| [foo| ... |] ==> $([foo| ... |])
| 
| (You could also allow $[foo| ... |] - i.e. you may omit the brackets)
| 
| In this proposal, you can then export "t" and "d" functions from
| Language.Haskell.TH with the type:
| 
| t :: String -> Type
| d :: String -> [Decl]
| 
| Which parse the provided string as Haskell. This allows existing any
| uses of Template Haskell to remain *unchanged* (as long as they
| imported the TH module :-). Otherwise rewrite them as:
| 
| [t|..|] ==> Language.Haskell.TH.t [|...|]
| 
| [d|...|] ==> Language.Haskell.TH.d [|...|]
| 
| (You could potentially special case these in the compiler to generate
| the result of the parse at compile time, rather than running the
| parser at runtime. This means that the staging behaviour of TH quotes
| can stay unchanged)
| 
| 
| CONCLUSION
| ===========
| 
| At the cost of changing the staging behaviour of [| |], [t| |] and [d|
| |] (usually, the parsing is done at compile time - in my proposal it
| is mostly done at runtime) and slightly changing the syntax:
|  1) QQ becomes an explicit splice, which is what it should have been
| in the first place.
|  2) QQ is revealed as the combination of two features: a new notation
| for String literals, and some extra overloading of the $() operator to
| deal with the QuasiQuote record
| 
| I rather like this proposal, even though I realise the chances of such
| a radical option being adopted are rather low.
| 
| Cheers,
| Dominic and Max
| 
| 2010/2/1 Simon Peyton-Jones <simonpj at microsoft.com>:
| > Dear GHC users
| >
| > This email is to announce two proposed changes to GHC's quasi-quotation
| mechanism.  For all I know, no one is using quasi-quotation (although it's a
| very cool feature, thanks to Geoff Mainland), but I didn't think I should
| take it for granted!
| >
| > The current spec is here:
| >        http://haskell.org/haskellwiki/Quasiquotation
| >        http://www.haskell.org/ghc/docs/latest/html/users_guide/template-
| haskell.html#th-quasiquotation
| >
| > A quasi-quote can appear as a (a) expression (b) pattern, and looks like
| this
| >        [$pads| ...blah... |]
| >
| > where 'pads' (of course any name will do) is a record of functions
| >   data QuasiQuoter = QuasiQuoter {
| >     quoteExp :: String -> Q Exp
| >     quotePat :: String -> Q Pat
| >   }
| >
| > The idea is that GHC evaluates (pads "...blah..."), and splices in the
| resulting Exp (or Pat) just as if that's what the user wrote in the first
| place.
| >
| > Kathleen Fisher has started to use this for her PADS system, and came up
| with two suggestions.
| >
| > 1. Allow quasi-quotes at the (top-level) declaration level, just like TH
| splices. So you could say, at top level
| >        [$pads| ...blah... |]
| > and have it expand to a bunch of top level Haskell declarations. This seems
| like an unconditionally good idea. To support it we'd need to add a field to
| QuasiQuoter:
| >   data QuasiQuoter = QuasiQuoter {
| >     quoteExp :: String -> Q Exp
| >     quotePat :: String -> Q Pat
| >     quoteDec :: String -> Q [Dec]
| >   }
| > but I don't think anyone will lose sleep over that.
| >
| > 2.  Make the notation less noisy for the "customer".  In particular, that
| '$' is scary, and redundant to boot.  She would like to write
| >        [pads| ...blah... |]
| >
| > I can see the motivation here, but there are two reasons for caution.
| >
| >  (i) The Template Haskell quote forms [t| ... |] and [d| ... |] behave
| >      rather differently.
| >
| >  (ii) If "[pads|" is a lexeme, then some list comprehensions become
| illegal, such
| >       as  [x|x<-xs,y<-ys].  But note that because of Template Haskell
| quotations,
| >       a comprehension [t|t<-ts] is already broken, and similarly with 'd',
| 'e'.
| >       So the proposed change will make things *more* uniform, by grabbing
| every
| >       "[blah|" as lexeme.
| >
| > For me (i) is the main issue.  The differences are significant.
| >  - A TH quote can appear only where an *expression* is expected
| >    But a quasiquote can be an expression or pattern or (assuming (1))
| declaration
| >
| >  - A TH quote has type (Q Typ) or (Q [Dec]) or (Q Exp)
| >    But a quasiquote is run immediately and spliced in place of the quote
| >
| >  - A TH splice is run during type checking
| >    But a quasiquote is run during renaming
| >
| > Even given all that, I'm strongly inclined to follow Kathleen's suggestion:
| >  - The differences are there all right, but in some ways the programmer
| thinks
| >    the same way:  [lang| blah |] switches to language 'lang'.
| >
| >  - Many users will never encounter the issue; they'll just say
| >        [pads| blah |]
| >    to wake up the PADS magic, and be oblivious to Template Haskell quotes
| >
| > An alternative would be to have some other cue. Ones I've considered
| >
| >  - $[pads| ...|], but allowing the $ to be omitted on top-level
| declarations,
| >    top level, just as it now can for TH splices.
| >
| >  - [pads:| ... |], with the colon distinguishing quasi-quoting from TH.
| >
| > My gut feel is to go with [|pads| ... |].  Of course this'd be a change
| from the current syntax, but I think there are few enough users that they'll
| switch easily enough.
| >
| >
| > Any comments on any of this?
| >
| > Simon
| >
| >
| >
| >
| > _______________________________________________
| > Glasgow-haskell-users mailing list
| > Glasgow-haskell-users at haskell.org
| > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
| >
| >



More information about the Glasgow-haskell-users mailing list