Lambda with invisible type pattern fails to splice with TemplateHaskell
I am using GHC 9.10.1-alpha1, which introduces @
-binders in more places in pattern contexts (!11109 (closed)). Here is an example of an expression one can write with this feature:
{-# LANGUAGE GHC2024 #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeAbstractions #-}
module Foo where
import Data.Kind
import Data.Proxy
f :: (forall (a :: Type). Proxy a) -> Proxy Bool
f k = k @Bool
g1 :: Proxy Bool
g1 = f (\ @a -> Proxy @a)
So far, so good. Now let's introduce a variant of g1
where the expression is spliced in via TemplateHaskell
:
g2 :: Proxy Bool
g2 = f $([| \ @a -> Proxy @a |])
I would expect this to typecheck just like g1
does. And yet, it doesn't:
$ ghc-9.10 Foo.hs
[1 of 1] Compiling Foo ( Foo.hs, Foo.o )
Foo.hs:16:9: error: [GHC-14964]
• Invisible type pattern a has no associated forall
• In the first argument of ‘f’, namely ‘(\ @a -> Proxy @a)’
In the expression: f (\ @a -> Proxy @a)
In an equation for ‘g2’: g2 = f (\ @a -> Proxy @a)
|
16 | g2 = f $([| \ @a -> Proxy @a |])
| ^^^^^^^^^^^^^^^^^^^^^^^^