Quasi quoting
Simon Marlow
marlowsd at gmail.com
Tue Feb 2 04:39:08 EST 2010
On 01/02/2010 14:25, Max Bolingbroke wrote:
> 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
Can you say precisely what it means to be "in an Exp context"? This is
a bit like Simon's type-directed name resolution idea, in that it's
adding in a bit of ad-hoc overloading. To understand this I think you
really need to write down (or at least sketch) the type system that
infers the context: e.g. you have to make clear what information is
taken into account (type signatures? the results of resolving other
overloading opportunities?).
> 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]
The TH library would have to include a Haskell parser, which presents
some engineering difficulties. TH can't be mutually recursive with GHC,
so either the haskell-src-exts package has to be used or TH and GHC have
to be merged.
Cheers,
Simon
More information about the Glasgow-haskell-users
mailing list