
#15815: problem with splicing type into constraint -------------------------------------+------------------------------------- Reporter: int-e | Owner: RyanGlScott Type: bug | Status: new Priority: highest | Milestone: Component: Template Haskell | Version: 8.6.1 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 RyanGlScott): Simpler example that only requires one module: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TemplateHaskell #-} module Bug where $([d| foo :: a ~ (Int -> Int) => a foo = undefined |]) }}} {{{ $ /opt/ghc/8.4.4/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) $ /opt/ghc/8.6.1/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:5:3: error: • Expected a type, but ‘a_a44c ~ Int’ has kind ‘Constraint’ • In the type signature: foo :: a_a44c ~ Int -> Int => a_a44c | 5 | $([d| foo :: a ~ (Int -> Int) => a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} Or, using fewer quotes: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH $(do foo <- newName "foo" a <- newName "a" pure [ SigD foo (ForallT [] [AppT (AppT EqualityT (VarT a)) (AppT (AppT ArrowT (ConT ''Int)) (ConT ''Int))] (VarT a)) , ValD (VarP foo) (NormalB (VarE 'undefined)) [] ]) }}} {{{ $ /opt/ghc/8.4.4/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) $ /opt/ghc/8.6.1/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:7:3: error: • Expected a type, but ‘a_a452 ~ Int’ has kind ‘Constraint’ • In the type signature: foo :: a_a452 ~ Int -> Int => a_a452 | 7 | $(do foo <- newName "foo" | ^^^^^^^^^^^^^^^^^^^^^^^... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15815#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler