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

GHC ghc-devs at haskell.org
Thu Mar 23 19:23:17 UTC 2017


#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


More information about the ghc-tickets mailing list