
#15815: problem with splicing type into constraint -------------------------------------+------------------------------------- Reporter: int-e | Owner: (none) Type: bug | Status: new Priority: normal | 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: | -------------------------------------+------------------------------------- Description changed by int-e: Old description:
Consider the following two-module example. (as gist: https://gist.github.com/int-e/a666991423c10150bd99dd0e874d6150) {{{#!hs {-# LANGUAGE TemplateHaskell #-} module A where
mkFoo tyQ = [d| foo :: a ~ $(tyQ) => a foo = undefined |] }}}
{{{#!hs {-# LANGUAGE TemplateHaskell, GADTs #-} module B where
import A
mkFoo [t| Int -> Int |] }}}
This loads fine in ghc-8.4.2, but with ghc-8.6.1 and current head (commit 578012be13eb1548050d51c0a23bd1a98423f03e), the splice goes wrong: {{{ $ ghci B.hs GHCi, version 8.6.1: http://www.haskell.org/ghc/ :? for help [1 of 2] Compiling A ( A.hs, interpreted ) [2 of 2] Compiling B ( B.hs, interpreted )
B.hs:7:1: error: • Expected a type, but ‘a_a4uD ~ Int’ has kind ‘Constraint’ • In the type signature: foo :: a_a4uD ~ Int -> Int => a_a4uD | 7 | mkFoo [t| Int -> Int |] | ^^^^^^^^^^^^^^^^^^^^^^^ Failed, one module loaded. *A> }}}
As a workaround one can define a type alias for the `Int -> Int` type.
New description: Consider the following two-module example. (as gist: https://gist.github.com/int-e/a666991423c10150bd99dd0e874d6150) {{{#!hs {-# LANGUAGE TemplateHaskell #-} module A where mkFoo tyQ = [d| foo :: a ~ $(tyQ) => a foo = undefined |] }}} {{{#!hs {-# LANGUAGE TemplateHaskell, GADTs #-} module B where import A mkFoo [t| Int -> Int |] }}} This loads fine in ghc-8.4.2, but with ghc-8.6.1 and current head (commit 23956b2ada690c78a134fe6d149940c777c7efcc), the splice goes wrong: {{{ $ ghci B.hs GHCi, version 8.6.1: http://www.haskell.org/ghc/ :? for help [1 of 2] Compiling A ( A.hs, interpreted ) [2 of 2] Compiling B ( B.hs, interpreted ) B.hs:7:1: error: • Expected a type, but ‘a_a4uD ~ Int’ has kind ‘Constraint’ • In the type signature: foo :: a_a4uD ~ Int -> Int => a_a4uD | 7 | mkFoo [t| Int -> Int |] | ^^^^^^^^^^^^^^^^^^^^^^^ Failed, one module loaded. *A> }}} As a workaround one can define a type alias for the `Int -> Int` type. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15815#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler