
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.htm... 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

Hi Simon,
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!
For info, My PhD student George Giorgidze and myself are using it for our EDSL Hydra for non-causal modelling and simulation of physical systems. Indeed, it is a very cool feature. Actually, for us, almost essential, as it gives us *principled* control over the syntax of the deep aspects of our embedding in a way that the usually embedding tricks just don't provide. We'll have a look. Thanks for letting us know! /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk

Dear all, George and I have been discussing this. We very much support the idea of allowing QQ for top-level definitions. Additionally, we think QQ should be allowed for *types*, just like TH, by extending the record of functions in the following way: data QuasiQuoter = QuasiQuoter { quoteExp :: String -> Q Exp quotePat :: String -> Q Pat quoteDec :: String -> Q [Dec] quoteType :: String -> Q Type } We have been discussing the need for this for some time, and if Kathleen hadn't effectively beaten us to it, we'd have made inquiries for the feasibility of such a facility shortly anyway. Additionally, this would make the functionality of TH and QQ more uniform. As to syntax, Both George and I prefer [name| ... |]. Yes, it clashes with list comprehensions, but users who use this facility just have to be aware of that caveat. And, as Simon says, this is already the case for TH. It is true that QQ in some ways is rather different from TH. But, from a user perspective, they're both about *meta programming*, and thus it makes sense to adopt a similar syntax for the two where "name" can be seen as a keyword to specify the kind of meta-programming one is doing. Including the empty string ([|) for the default case, basic TH expressions. Best, George and Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk

(ii) If "[pads|" is a lexeme, then some list comprehensions become illegal,
I am not myself a TH or QQ user, but it has always bothered me slightly that the syntax for them steals some valid list comprehensions. Of the alternative syntaxes you suggest...
My gut feel is to go with [|pads| ... |].
... this one feels the nicest, because [| |] is an ascii approximation of the common syntactic brackets used in semantic specifications. In some ways, to make the correspondence even closer, pads [| ... |] might be even better, although I realise that this might present new problems. Regards, Malcolm

Hi, I've been experimenting with quasiquoting, and would like to see both of Kathleen's suggestions adopted. The top level quasi quotes would be useful, and reducing the notational noise would be very nice. I don't see the issue of stealing some currently-valid list comprehensions as very serious. Since [t|t<-ts] and other forms are gone, I've come to think of the syntax [foobar| as already taken for all foobar. The loss here seems minimal but the gain is that DSLs can look more natural. John O'Donnell -----Original Message----- From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] On Behalf Of Simon Peyton-Jones Sent: 01 February 2010 06:51 To: glasgow-haskell-users@haskell.org Cc: Kathleen Fisher; mainland@eecs.harvard.edu Subject: Quasi quoting 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.htm... 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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users The University of Glasgow, charity number SC004401

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
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.htm...
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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

(Sorry if you see this twice, Simon - I didn't reply to the list)
2010/2/2 Simon Marlow
Can you say precisely what it means to be "in an Exp context"?
In a Type context == a HsSpliceTy constructor in the existing GHC AST In an Exp context == a HsSpliceE constructor in the existing GHC AST In a Decl context == a SpliceD constructor in the existing GHC AST
This is a bit like Simon's type-directed name resolution idea, in that it's adding in a bit of ad-hoc overloading.
I don't think so - it's much easier to deal with than that. What sort of context the splice is in is purely syntactic, and we already have to work it out to implement the existing Template Haskell semantics. Our proposal does not complicate this at all.
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.
This is a real issue. Using src-exts would be a good fix, especially because it would mean that the numerous tools and libraries that already use the src-exts data structure could be reused in your TH programs. Unfortunately it would either: a) Have to be a boot package, so that GHC can translate the spliced Exp or whatever into GHC's HsExpr b) Or we could let $() accept a HsExpr (exported by the GHC package). Users can then use src-exts as a non-boot package, along with another non-boot package similar to src-exts-meta (see Hackage) which translates src-exts types into the GHC ones for the splice. This would let us delete a lot of code from GHC (DsMeta, Covert..). It's a big change though, and I'm not sure how I feel about it. Cheers, Max

On 02/02/2010 15:40, Max Bolingbroke wrote:
(Sorry if you see this twice, Simon - I didn't reply to the list)
2010/2/2 Simon Marlow
: Can you say precisely what it means to be "in an Exp context"?
In a Type context == a HsSpliceTy constructor in the existing GHC AST In an Exp context == a HsSpliceE constructor in the existing GHC AST In a Decl context == a SpliceD constructor in the existing GHC AST
Ah ok, that's fine then. Cheers, Simon

Max Bolingbroke wrote:
... 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 [|...|]
I'm concerned in both your proposals, that single-letter names like "t" and "d" are common function parameters, thus possibly producing - shadowing warnings for all such functions in modules that happen to use TH - errors, I think, for some uses of TH inside such functions (either the function parameters must be renamed, or the TH splice module-qualified) -Isaac

2010/2/2 Isaac Dupree
I'm concerned in both your proposals, that single-letter names like "t" and "d" are common function parameters, thus possibly producing - shadowing warnings for all such functions in modules that happen to use TH - errors, I think, for some uses of TH inside such functions (either the function parameters must be renamed, or the TH splice module-qualified)
Yes, this is certainly an annoyance :-). However, we didn't have backcompat high up the list of priorities with these proposals - instead we wanted to look at how TH and QQ might be redesigned to work together a bit more neatly if we were starting with a clean slate today. You can of course choose more expressive names than "e" and "t" if you're going to break backcompat anyway, Cheers, Max

Hello Max, Tuesday, February 2, 2010, 7:25:36 PM, you wrote:
You can of course choose more expressive names than "e" and "t" if you're going to break backcompat anyway,
i propose x and xs :D -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Max Bolingbroke wrote:
2010/2/2 Isaac Dupree
: I'm concerned in both your proposals, that single-letter names like "t" and "d" are common function parameters, thus possibly producing - shadowing warnings for all such functions in modules that happen to use TH - errors, I think, for some uses of TH inside such functions (either the function parameters must be renamed, or the TH splice module-qualified)
Yes, this is certainly an annoyance :-). However, we didn't have backcompat high up the list of priorities with these proposals - instead we wanted to look at how TH and QQ might be redesigned to work together a bit more neatly if we were starting with a clean slate today.
You can of course choose more expressive names than "e" and "t" if you're going to break backcompat anyway,
You could also do away with these names entirely, and use magic instead: instance IsString HsExpr where fromString = e Or perhaps a different typeclass for [|...|] blocks, class Quoted a where parseQuote :: String -> a -- for performance reasons: parseQuote' :: Ghc.PackedString -> a This also leaves the door open for constructions like: instance Quoted QuasiQuote where parseQuote xs = let (f,x) = splitAt '|' xs in (findParserByName f) x f = $[|foo| ... |] -- we still have to register foo somehow Twan

2010/2/2 Twan van Laarhoven
class Quoted a where parseQuote :: String -> a -- for performance reasons: parseQuote' :: Ghc.PackedString -> a
Great idea! Thinking about it, you can use type classes to dispose of the QuasiQuote record entirely. Instead, have: class MyLang a where myLang :: String -> Q a instance MyLang Exp where myLang = myLangSyntaxToGHCExprForSplice . myLangExpParser ... etc, MyLang instances for Pat and Type too ... And then write: $(myLang [|...|]) Now the splice $(e) typechecks e as a Q Type / Q Exp / Q Decl as required by the context it is in, and hence gets the correct instance of MyLang. So our proposal needn't change the semantics of splice at all - we can reuse the name overloading abilities of type classes. It's a shame that TH is too widely used to be amenable to refactoring into this sort of form. Cheers, Max

On Feb 3, 2010, at 1:48 AM, Max Bolingbroke wrote:
2010/2/2 Twan van Laarhoven
: class Quoted a where parseQuote :: String -> a -- for performance reasons: parseQuote' :: Ghc.PackedString -> a
Great idea!
Thinking about it, you can use type classes to dispose of the QuasiQuote record entirely. Instead, have:
class MyLang a where myLang :: String -> Q a
instance MyLang Exp where myLang = myLangSyntaxToGHCExprForSplice . myLangExpParser
... etc, MyLang instances for Pat and Type too ...
With a class-based approach only one parser that creates values of the same type could be used in a program. It would not be possible to embed multiple languages that create TH.Exp to be spliced into a single program. With the current syntax, I can write [$myLang| ... |] and [$yourLang| ... |] in the same program and use different parsers although both create Exp values.
And then write:
$(myLang [|...|])
This is more verbose than the proposed [myLang| ... |]. There seem to be different goals in the different proposals in this thread: 1. Simplify the syntax for quasi quoting (remove $, use different brackets), 2. make it more generally applicable (allow declarations and/or types to be quasi quoted), and 3. simplify and generalise its implementation (invent a single mechanism that unifies quasi quoting and TH splicing). Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On 3 February 2010 14:07, Sebastian Fischer
With a class-based approach only one parser that creates values of the same type could be used in a program. It would not be possible to embed multiple languages that create TH.Exp to be spliced into a single program. With the current syntax, I can write [$myLang| ... |] and [$yourLang| ... |] in the same program and use different parsers although both create Exp values.
This is not the case, because you still have an instance "Quoted String". Then you can write: $(myLang [|..|]) Where myLang :: String -> Q Exp The "Quoted Exp" instance you have in scope just determines what default semantics for $([|...|]) you get! So you can use this behaviour to change the default "language" from Haskell to whatever you like, but importing a My.Lang.Module rather than Language.Haskell.TH. This is a bit ugly though, and is more of an unintentional feature than something I was designing for :-)
This is more verbose than the proposed [myLang| ... |]. There seem to be different goals in the different proposals in this thread: 1. Simplify the syntax for quasi quoting (remove $, use different brackets), 2. make it more generally applicable (allow declarations and/or types to be quasi quoted), and 3. simplify and generalise its implementation (invent a single mechanism that unifies quasi quoting and TH splicing).
Yes - I should have made it clearer that our proposal had strayed rather far from the original goal of reducing verbosity :-). Instead it increases it in the QQ case - but in (IMHO) a good way. Cheers, Max

On Feb 3, 2010, at 6:13 PM, Max Bolingbroke wrote:
With a class-based approach only one parser that creates values of the same type could be used in a program.
This is not the case, because you still have an instance "Quoted String". Then you can write:
$(myLang [|..|])
Where myLang :: String -> Q Exp
Ah, you're right. I find an instance Quoted String a little confusing and would probably write $(myLang "..") instead. Hmm, this is more complicated if the string contains line breaks and [|..|] would be an alternative string literal syntax where line breaks don't need to be escaped. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On February 2, 2010 19:48:27 Max Bolingbroke wrote:
It's a shame that TH is too widely used to be amenable to refactoring into this sort of form.
I thought the standard thing to do in this case was to add either a pragma that gives you the new behaviour or trigger it with an alternative syntax (such as the aforementioned (|...|)). Throw in a warning whenever the old is used, and then, after a couple of years/releases, you can depreciate support for it guilt free. : ) Cheers! -Tyson

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@gmail.com [mailto:omega.theta@gmail.com] On Behalf Of Max
| Bolingbroke
| Sent: 01 February 2010 14:25
| To: Simon Peyton-Jones
| Cc: glasgow-haskell-users@haskell.org; Kathleen Fisher;
| mainland@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

Hello,
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!
As a point of reference, we are using quasi-quotation extensively in our machinery for generating Javascript, which we also put on Hackage as the jmacro package. A small syntax change probably wouldn't be a big deal for us. We'll think about the other proposed changes some more and offer some comments if we have anything interesting to say. thanks for the warning, Jeff --- This communication may contain confidential and/or privileged information. If you are not the intended recipient (or have received this communication in error) please notify the sender immediately and destroy this communication. Any unauthorized copying, disclosure or distribution of the material in this communication is strictly forbidden. Deutsche Bank does not render legal or tax advice, and the information contained in this communication should not be regarded as such.

I like (1) quite a lot. If radical suggestions for QQ noise reduction are being entertained, here's another: quotations of the form [| .... |] (i.e. no 'language' specified) will use an implicit parameter* ('quasi', say) of type QuasiQuoter, if in scope. Otherwise, they will behave as they currently do (TH expression quotation?). Now to awaken the 'pads' magic (or some other magic), you'd do this somewhere: quasi = pads and then all your [| .... |]'s would be pads expressions/patterns/declarations. Rob * - implicit parameters fill me with a nameless dread under normal circumstances.

| quotations of the form [| .... |] (i.e. no 'language' specified) will
| use an implicit parameter* ('quasi', say) of type QuasiQuoter, if in
| scope. Otherwise, they will behave as they currently do (TH
| expression quotation?). Now to awaken the 'pads' magic (or some other
| magic), you'd do this somewhere:
|
| quasi = pads
Nice idea, but won't work as specified. The thing is that the quasiquoter is run at *compile time*. So it can't be an implicit parameter, which is by definition only available at runtime
f :: (?q:QuasiQuoter) => ..blah...
A variant of your suggestion would be: for any quote [|..blah..|] behave as if the programmer had written [quasiQuoter| ...blah...|]. That is, simply pick up whatever record named "quasiQuoter" is in scope. Then you'd say
import Pads( quasiQuoter )
and away you go. But you can only use one at a time.
That might be quite convenient, but alas [|...|] has already been taken by Template Haskell quotes, meaning [e| ...|]. So you'd need something else. [*|...|] perhaps.
Or we could switch to different quotation brackets altogether for quasiquotation, the obvious possibility being <|...blah...|>, and

Hi all, Simon wrote (answering Robert Greayer):
A variant of your suggestion would be: for any quote [|..blah..|] behave as if the programmer had written [quasiQuoter| ...blah...|]. That is, simply pick up whatever record named "quasiQuoter" is in scope. Then you'd say import Pads( quasiQuoter ) and away you go. But you can only use one at a time.
Yes, I can see that (or one of the alternative forms proposed) would sometimes be convenient. But, being explicit about *which* syntax one is switching into does arguably enhance readability. Without this cue, the reader have to hunt for the appropriate binding before he or she can make sense of a piece of quasiquoted text. Also, as Simon suggests, being explicit makes it possible to use more than one quasiquoter at a time (in one module). Potentially quite useful. I can see being explicit about which quasiquoterbeing to use would be a bit of an issue in a setting with lots of very small fragments being spliced in all over the place. But at least in our experience, and what we've seen in Geoffrey's papers, quiasiquoted code fragments tend to be relatively substantial, where naming the quasiquoter doesn't add much overhead at all. Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn@cs.nott.ac.uk

A variant of your suggestion would be: for any quote [|..blah..|] behave as if the programmer had written [quasiQuoter| ...blah...|]. That is, simply pick up whatever record named "quasiQuoter" is in scope. Then you'd say import Pads( quasiQuoter ) and away you go. But you can only use one at a time.
That might be quite convenient, but alas [|...|] has already been taken by Template Haskell quotes, meaning [e| ...|]. So you'd need something else. [*|...|] perhaps.
Would it be possible to have [| ... |] mean [quasiQuoter| ... |] iff a 'quasiQuoter' has been imported, but otherwise mean [e| ... |]? Or does the determination to treat [something| .. blah .. |] as a quasi quote need to be made before it is possible to determine if there really is a 'something' available to process the quasi quote? You could also explicitly rely on the presence/absence of the QuasiQuotes and TemplateHaskell language options (iff QQ is on, [| ... |] means [quasiQuoter| ... |], forcing the explicit [e| ... |] for TH expression quotes). Better for one extension to steal syntax from another, perhaps, than stealing it from the base language. As Henrik points out (in his parallel reply) this only really matters if your quasi-quoted strings are quite short. I only recently came up with a use case in which a really terse quasi-quotation would be helpful; heretofore lengthy quotations were all that I had used. Nevertheless, the proposal as it stands would allow me to get away with a quasi-quotation that's only one character less terse than my 'implicit' suggestion would allow. Thanks, Rob

2010/02/01 Simon Peyton-Jones
That might be quite convenient, but alas [|...|] has already been taken by Template Haskell quotes, meaning [e| ...|]. So you'd need something else. [*|...|] perhaps.
Why is that a problem? Would TH and quasi-quoting be likely to be enabled at the same time? One could decide in favour of QQs if they are enabled (though yes, this is likely horrible on the inside).
Or we could switch to different quotation brackets altogether for quasiquotation, the obvious possibility being <|...blah...|>, and
. [...]
It's true; but I suspect `<|' and `|>' are actually widely used. Wouldn't `(|' and `|)' be safer? In either case, it's easy to see how me evolve an indentational quasi-quote syntax: `[|]' or `(|)'. If the default quasi-quoter is simple string literals, then there's no need for a HEREDOC in the language. -- Jason Dusek

On Feb 1, 2010, at 11:46 PM, Jason Dusek wrote:
Wouldn't `(|' and `|)' be safer?
I like this suggestion. It avoids conflicts with Template Haskell and list comprehensions. Conor McBride also picked these brackets as idiom brackets in his preprocessor she. [$blah| ... |] could be replaced with (blah| ... |) and (| ... |) could be syntactic sugar for (quote| ... |) and use whatever definition of quote is in scope. Would this introduce severe ambiguities? I can think of (foo||bar) where you need to go to the end to see that it does not end in |). Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Dear Simon, I want to generate data type declarations using quasi quotes and hence support the proposal to allow quasi quotation at declaration level. With respect to syntax, I'd prefer [|blah| ... |] over the current [$blah| ... |] and would also be fine with [blah| ... |]. What is the reason to restrict quasi quotation to top-level declarations rather than letting it also generate local declarations? Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

| What is the reason to restrict quasi quotation to top-level | declarations rather than letting it also generate local declarations? Local declarations for quasi-quotation would be possible too: f x = v where [pads| ..blah..|] But it's a bit more complicated to implement. And a Q [Dec] could produce type and class declarations, which can't appear nested; that would be rejected, but it feels uncomfortable. So, reasonable suggestion, but I think I'll wait till we have a serious customer for this before taking it further. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell- | users-bounces@haskell.org] On Behalf Of Sebastian Fischer | Sent: 02 February 2010 11:04 | To: Simon Peyton-Jones | Cc: glasgow-haskell-users@haskell.org; Kathleen Fisher; | mainland@eecs.harvard.edu | Subject: Re: Quasi quoting | | Dear Simon, | | I want to generate data type declarations using quasi quotes and hence | support the proposal to allow quasi quotation at declaration level. | With respect to syntax, I'd prefer [|blah| ... |] over the current | [$blah| ... |] and would also be fine with [blah| ... |]. | | What is the reason to restrict quasi quotation to top-level | declarations rather than letting it also generate local declarations? | | Sebastian | | | -- | Underestimating the novelty of the future is a time-honored tradition. | (D.G.) | | | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (14)
-
Bulat Ziganshin
-
Henrik Nilsson
-
Isaac Dupree
-
Jason Dusek
-
Jeff Polakow
-
John O'Donnell
-
Malcolm Wallace
-
Max Bolingbroke
-
Robert Greayer
-
Sebastian Fischer
-
Simon Marlow
-
Simon Peyton-Jones
-
Twan van Laarhoven
-
Tyson Whitehead