[GHC] #10047: inconsistency in name binding between splice and quasiquotation

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.4 Haskell | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Let me preface this by saying that this may not be a bug. If not then it would be nice if the documentation for Template Haskell could clarify what's going on here. My understanding of quasiquotation is that a quasiquote `[n|foo|]` is equivalent to a splice `$(quoteExp n "foo")`. However, that is not the case in all contexts. {{{ module Q where import Language.Haskell.TH import Language.Haskell.TH.Quote n = QuasiQuoter { quoteExp = dyn } }}} {{{ rwbarton@morphism:/tmp$ ghci -XTemplateHaskell -XQuasiQuotes Q GHCi, version 7.8.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Q ( Q.hs, interpreted ) Q.hs:6:5: Warning: Fields of ‘QuasiQuoter’ not initialised: quotePat, quoteType, quoteDec In the expression: QuasiQuoter {quoteExp = dyn} In an equation for ‘n’: n = QuasiQuoter {quoteExp = dyn} Ok, modules loaded: Q. *Q> :t [| $(dyn "foo") |] [| $(dyn "foo") |] :: ExpQ *Q> :t [| [n|foo|] |] Loading package pretty-1.1.1.1 ... linking ... done. Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package containers-0.5.5.1 ... linking ... done. Loading package template-haskell ... linking ... done. <interactive>:1:7: Not in scope: ‘foo’ In the Template Haskell quotation [| [n|foo|] |] }}} Why do these behave differently? (Lastly, the link to the paper "Why It's Nice to be Quoted: Quasiquoting for Haskell" in the User's Guide at https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/template- haskell.html#th-quasiquotation is broken. Does this paper have a permanent home? In any case, I only skimmed it but it didn't seem to answer my question.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 7.8.4
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => th/T10047 * resolution: => fixed * milestone: => 7.12.1 Comment: Very good bug report thank you. Now properly fixed. It's a big-ish change, and includes a simplification in the hooks API, so probably not for 7.10. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Did you forget to add `./th/T10047.run.stderr`? I observe {{{ Actual stderr output differs from expected: --- /dev/null 2014-07-11 16:48:13.679453102 +0200 +++ ./th/T10047.run.stderr 2015-02-10 19:42:50.001947139 +0100 @@ -0,0 +1,6 @@ + +T10047.hs:6:5: Warning: + Fields of ‘QuasiQuoter’ not initialised: quotePat, quoteType, + quoteDec + In the expression: QuasiQuoter {quoteExp = dyn} + In an equation for ‘n’: n = QuasiQuoter {quoteExp = dyn} *** unexpected failure for T10047(ghci) }}} on https://raw.githubusercontent.com/nomeata/ghc-speed- logs/master/f46360ed7139ff25741b381647b0a0b6d1000d84.log -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner:
Type: bug | Status: closed
Priority: normal | Milestone: 7.12.1
Component: Template Haskell | Version: 7.8.4
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case: th/T10047
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda): This has broken the name resolution behavior for quasiquoters. Previously, this was valid (assuming "wow" is a quasiquoter producing a declaration): {{{ {-# LANGUAGE QuasiQuotes #-} thing = okay [wow|stuff|] okay = 3 }}} but now it produces an error: {{{ /tmp/runghcXXXX1804289383846930886.hs:3:9: error: Not in scope: ‘okay’ }}} because after this change, quasiquoters share the declaration order restrictions of splices. I have code that depends on the previous behavior, and I'm sure there's a lot more code out there that does as well, as this was one of the main advantages of using quasiquoters over regular splices. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by spinda): * status: closed => new * resolution: fixed => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): spinda: indeed, your example hints at a simpler manifestation of the bug; when `wow` runs in your program, `thing` is not accessible to `reify` (not in scope), whereas if you'd written a splice with `$(...)`, it would be in scope. Sorry to hear that your programs were broken by this fix, but can't you just move the quasiquotations upward in your file so that they aren't in the middle of any recursive definition groups (e.g., to the top of the file)? I'm pretty sure the main advantage of quasiquoters was supposed to be the succinct syntax, not an undocumented difference in scoping rules. If there's a real use case for a type of splice with different scoping, it doesn't particularly make language design sense to tie that difference to quasiquotes vs. traditional splices. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Reid is, as usual, spot on. The big deal about quasiquotes is that they save you writing `$(wow "blah")`. It's interesting that the (entirely accidental) change in scoping is "one of the main advantages of using quasi-quoters". Can you say why it's so important? Quasi-quoters may use anti-quotation: {{{ xs = blah [wow| funny language `(reverse xs)` blah |] }}} Here `wow` might use back-quotes to trigger anti-quotation, and then use `reify` to look up `reverse` and `xs`. So we'd need them to be in scope. It's not ridiculous to propose the scoping you want for declaration splices; it could be something like * bring all the binders into scope (`thing` and `okay` in your example) * run the quasi-quote * splice it in But someone would need to work out the details. Eg if there were two quasiquotes, what would each see in its reification environment. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda): Firstly, at least as far as I've seen, the scoping restriction is one of the most common complaints about Template Haskell splices, as using them at all suddenly causes order of declaration to matter where it didn't before. This contributes to the stigma and avoidance of Template Haskell usage. It would be a shame to see quasiquoters get shackled with this issue as well. Then, I think it's important to consider the role of quasiquoters as enabling extensions to the language without requiring compiler plugins, external preprocessors, or what have you, while keeping them contained from the rest of the Haskell source around them. As a specific example, I'll pull from my current GSoC project, which is impacted by this change (and, to be honest, is the reason I ran into this). I have an {{{lq}}} quasiquoter which allows for LiquidHaskell type signatures and specifications to be attached to variables and types. In the declaration context, it parses a subset of Haskell with LiquidHaskell extensions and emits declarations and annotations. Take some vanilla Haskell code: {{{ module Test () where type Nat = Int add :: Nat -> Nat -> Nat add x y = id' $ x + y id' :: a -> a id' x = x }}} A little contrived, but not too far from what you'd run into in sufficiently complex real-world projects. Under the current (or, previous) quasiquoter implementation, extending this existing code with custom annotations is a fairly straightforward translation: {{{ {-# LANGUAGE QuasiQuotes #-} module Test () where import LiquidHaskell [lq| type Nat = { v:Int | 0 <= v } |] [lq| add :: Nat -> Nat -> Nat |] add x y = id' $ x + y [lq| id' :: x:a -> { v:a | v == a } |] id' x = x }}} But after this change, introducing these annotations suddenly makes order of declaration matter. What were lightweight inline extensions to the language now require restructuring of code, either reordering the functions themselves or moving all signatures and specifications to the top of every file. Needless to say, this makes the whole thing much less attractive. And, frankly, this is what quasiquoters are all about: lightweight, inline language extensions that don't interfere with the rest of the code. This intent is reflected in the original paper. With this restriction imposed, anything using quasiquoters suddenly brings in a lot more baggage than it used to, discouraging use. It's not just a matter of modifying some existing code to fit, it's that this hampers a whole set of use-cases for which quasiquoters (a) used to fit quite nicely and (b) are the only real solution at present. Quietly breaking this behavior of 12 years now in a tangentially related bugfix strikes me as, well, wrong, especially when there isn't an alternative available. Excuse me if I seem rather passionate about this issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda): Sorry, I should add that I'm not opposed to change here, as long as a viable alternative that preserves these use cases makes it in at the same time. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda):
Quasi-quoters may use anti-quotation:
{{{ xs = blah [wow| funny language `(reverse xs)` blah |] }}}
Is this a new feature? It doesn't seem to be present as of 7.10.1. (Apologies for the multiple consecutive replies.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda): re: what multiple declaration splices would see in their reification environments, the current behavior for quasiquoters seems to be to evaluate declaration quasiquoters in the order of appearance in the source. So decalarations produced by a declaration splice further up the file would make it into the reification environments of subsequent declaration splices. Declarations produced by splices lower down would be invisible to ones further up. This seems reasonable to me, as long as the scoping restriction is contained within the TH/quasiquoter processing and doesn't leak out over the rest of the source. I'm likely overlooking a deeper issue here, so please let me know what else would need to be addressed. re: anti-quotation in quasiquoters, I think I misunderstood simonpj's comment the first time around. If I understand correctly now, this isn't referring to some new native support for antiquotation, but rather an example of how a quasiquoter would come to use {{{reify}}}. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by slyfox): * cc: slyfox (added) Comment: I skimmed through testsuite failures on full validate today and found qq007 and qq008 failures: {{{#!hs [sf] ~/dev/git/ghc/testsuite/tests/quasiquotation/qq007:cat QQ.hs {-# LANGUAGE TemplateHaskell #-} module QQ where import Language.Haskell.TH.Quote import Language.Haskell.TH pq = QuasiQuoter { quoteDec = \_ -> [d| f x = x |], quoteType = \_ -> [t| Int -> Int |], quoteExp = \_ -> [| $(varE (mkName "x")) + 1::Int |], quotePat = \_ -> [p| Just x |] } [sf] ~/dev/git/ghc/testsuite/tests/quasiquotation/qq007:"/home/slyfox/dev/git/ghc/inplace/bin /ghc-stage2" --make Test -fforce-recomp -dcore-lint -dcmm-lint -dno- debug-output -no-user-package-db -rtsopts -fno-warn-tabs -fno-ghci-history -v0 Test.hs:6:1: error: The type signature for ‘f’ lacks an accompanying binding }}} Reid suggested this fix likely caused the change. Is it fine/expected? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda): Regarding what I wrote earlier about the splicing restriction: There's an essential conflict between having module-local declarations in scope for the reification environment and avoiding the splitting of declaration groups on splices. For some splices, such as {{{makeLenses}}}, reification takes precedence. But not all splices need to reify module- local declarations: for those, giving that up would be worth avoiding the splicing restriction. In 7.10, the first use case for splices is covered by the {{{$(...)}}} syntax, and the second by quasiquoters. After this change, only the first is represented. This can be rectified by providing some way to mark splices as falling into the second category, then processing them along with the other declarations in the group instead of splitting on them. To accomplish this, an additional {{{$$(...)}}} syntax (or similar) could be added. In the top-level declaration context, these splices would be marked as not to be split on. For consistency, the same syntax would yield the same result as {{{$(...)}}} in all other contexts (types, etc). Quasiquoters would then gain a similar additional syntax, {{{[:name| ... |]}}} or such. Since this would actually emulate the current behavior of quasiquoters, perhaps the effect should be reversed here for compatibility, with the second syntax ''enabling'' splitting. I'm not sure. Alternately, we could forgo the additional syntax and simply mark all splices arising from quasiquoters as not causing a split. This would accomplish the end goal of preserving compatibility. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:13 slyfox]:
I skimmed through testsuite failures on full validate today and found qq007 and qq008 failures:
These failures are indeed due to this ticket -- we need to fix them up. But first, we have to decide what to do with this ticket in general. I have to say I find @spinda's arguments convincing. The idea that `[q|blah|]` is identical to `$(quoteDec q "blah")` is nice, but perhaps there is a reason for two separate mechanisms here. The splitting that @spinda is so worried about happens only for ''declaration'' splice/quasiquotes, so we could have the splices/quasiquote consistency for other contexts. With some careful documentation in the manual, I think it's not hard for users to understand this difference. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.12.1
Component: Template Haskell | Version: 7.8.4
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case: th/T10047
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Thomas Miedema

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T10047 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): See #5463 for another scenario where having flexibility around the issue discussed here would be helpful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: spinda Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T10047 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1199 -------------------------------------+------------------------------------- Changes (by spinda): * owner: => spinda * differential: => Phab:D1199 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10047: inconsistency in name binding between splice and quasiquotation
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: spinda
Type: bug | Status: new
Priority: normal | Milestone: 7.12.1
Component: Template Haskell | Version: 7.8.4
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case: th/T10047
Blocked By: | Blocking:
Related Tickets: | Differential Revisions: Phab:D1199
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: spinda Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T10047 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1199 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10047#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC