[GHC] #13473: Variables in patterns made with QuasiQuotes sometimes don't get bound

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In GHCi 8.0.2 {{{
import Language.Haskell.TH import Language.Haskell.TH.Quote :set -XQuasiQuotes quoter = QuasiQuoter { quotePat = varP . mkName } [quoter|x|] = 1 x error: Variable not in scope: x }}}
I think "x" ought to be 1. Previous versions of GHCi don't let me be so free about defining and using quasiquotes, so here is a minimal example with modules: {{{ -- In QQ.hs module QQ where import Language.Haskell.TH import Language.Haskell.TH.Quote quoter :: QuasiQuoter quoter = QuasiQuoter { quotePat = varP . mkName } }}} and {{{ -- In Main1.hs module Main1 where import QQ [quoter|x|] = 1 main = print x }}} With GHC 7.10.3 this compiles (and prints "1" when run), but in GHC 8.0.2 this complains "x" is not in scope. The same problem manifests itself when the pattern quasi quote is used in a "let" binding. Peculiarly, this appears ''not'' to affect cases where the pattern is a function argument. The following compiles and runs (printing "1") on both 7.10.3 and 8.0.2. {{{ -- In Main2.hs module Main2 where import QQ f [quoter|x|] = x main = print (f 1) }}} I understand there were some changes around splices and declaration groups (which presumably are part of why GHCi plays with quasi quotes), so I'm not sure this is really a bug! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13473 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by harpocrates): Actually, it looks like this is equivalent to a more general TH issue (with a smaller minimal example). The following compiles in 7.10.3 but not 8.0.2 {{{ {-# LANGUAGE TemplateHaskell #-} module Main where import Language.Haskell.TH main = let $(varP $ mkName "x") = 1 in print x }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13473#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound
-------------------------------------+-------------------------------------
Reporter: harpocrates | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.0.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* cc: facundominguez (added)
* component: Compiler => Template Haskell
Comment:
This regression appeared between GHC 8.0.1 and 8.0.2. I tracked it down to
commit 8d63419478074728eb03082787ea51d498b3e62e:
{{{
From 8d63419478074728eb03082787ea51d498b3e62e Mon Sep 17 00:00:00 2001
From: =?utf8?q?Facundo=20Dom=C3=ADnguez?=

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: facundominguez (removed) * cc: facundo.dominguez (added) Comment: Oops, I cc'd the wrong username, it seems. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13473#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3572 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3572 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13473#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound
-------------------------------------+-------------------------------------
Reporter: harpocrates | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.0.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3572
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3572 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Thanks, Ryan. Please, excuse me for not looking at this earlier. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13473#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3572 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * milestone: => 8.2.1 Comment: No worries, Facundo! I'll optimistically mark this is merge, since it seems to be a straightforward bugfix. Feel free to close if you think otherwise. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13473#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13473: Variables in patterns made with QuasiQuotes sometimes don't get bound -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3572 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged with 72015aba0af37e0547150299049591e2a0ced270. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13473#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC