Template Haskell mistakenly assumes "FUN" is built-in syntax
Basically the same issue as #24702 (closed) but with "FUN"
.
The following works as expected:
{-# LANGUAGE TemplateHaskell #-}
module T where
import Language.Haskell.TH
data Fun a b = MkFun (a -> b)
evenFun :: $(conT (mkName "Fun")) Int Bool
evenFun = MkFun even
[1 of 1] Compiling T ( Test.hs, interpreted )
Ok, one module loaded.
But if Fun
is capitalized, it results in a bogus error:
{-# LANGUAGE TemplateHaskell #-}
module T where
import Language.Haskell.TH
data FUN a b = MkFUN (a -> b)
evenFUN :: $(conT (mkName "FUN")) Int Bool
evenFUN = MkFUN even
[1 of 1] Compiling T ( Test.hs, interpreted )
Test.hs:8:12: error: [GHC-83865]
• Expecting one more argument to ‘GHC.Prim.FUN Int Bool’
Expected a type, but ‘GHC.Prim.FUN Int Bool’ has kind ‘* -> *’
• In the type signature: evenFUN :: GHC.Prim.FUN Int Bool
|
8 | evenFUN :: $(conT (mkName "FUN")) Int Bool
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Test.hs:8:35: error: [GHC-83865]
• Expected kind ‘GHC.Types.Multiplicity’, but ‘Int’ has kind ‘*’
• In the first argument of ‘GHC.Prim.FUN’, namely ‘Int’
In the type signature: evenFUN :: GHC.Prim.FUN Int Bool
|
8 | evenFUN :: $(conT (mkName "FUN")) Int Bool
| ^^^
Failed, unloaded all modules.
I'll submit a fix.