
#13608: Expose the type of quasiquotes -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: QuasiQuotes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 12778 | Differential Rev(s): Phab:D3610 Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Looks like typed splices and quasiquotes will pose some gotchas. {{{ -- Q.hs {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module Q where import Data.Proxy import Language.Haskell.TH.Syntax class C a where method :: Proxy a -> Q (TExp a) instance C Int where method _ = [|| 1 :: Int ||] instance C Char where method _ = [|| 'a' ||] q :: forall a. C a => Q (TExp a) q = method (Proxy :: Proxy a) }}} {{{ -- testQ.hs {-# LANGUAGE TemplateHaskell #-} import Q main :: IO () main = print ($$(q) `asTypeOf` (0 :: Int)) }}} {{{ $ ghc --make testQ.hs [1 of 2] Compiling Q ( Q.hs, Q.o ) [2 of 2] Compiling Main ( testQ.hs, testQ.o ) testQ.hs:6:18: error: • Ambiguous type variable ‘a0’ arising from a use of ‘q’ prevents the constraint ‘(C a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance C Char -- Defined at Q.hs:14:10 instance C Int -- Defined at Q.hs:11:10 • In the expression: q In the Template Haskell splice $$(q) In the first argument of ‘asTypeOf’, namely ‘$$(q)’ | 6 | main = print ($$(q) `asTypeOf` (0 :: Int)) | ^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13608#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler