problem with splicing type into constraint
Consider the following two-module example. (as gist: https://gist.github.com/int-e/a666991423c10150bd99dd0e874d6150)
{-# LANGUAGE TemplateHaskell #-}
module A where
mkFoo tyQ = [d|
foo :: a ~ $(tyQ) => a
foo = undefined
|]
{-# 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 23956b2a), 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.
Edited by Bertram Felgenhauer