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

GHC ghc-devs at haskell.org
Sat Jun 20 17:54:29 UTC 2015


#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


More information about the ghc-tickets mailing list