Change in TemplateHaskellQuotes behavior in 9.10 w.r.t. UnboundVarE
Consider this program:
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
module Bug where
import Control.Monad.IO.Class
data (%%%)
$(do e <- [e| (%%%) |]
liftIO $ putStrLn $ show e
pure [])
Note that [e| (%%%) |]
quotes the name %%%
in an expression context. Since there isn't a term-level %%%
name in scope, I would expect this to turn unto UnboundVarE %%%
. In GHC 9.8 and earlier, this is what happens:
$ ghc-9.8 Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
UnboundVarE %%%
In GHC 9.10, however, this doesn't happen:
$ ghc-9.10 Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
ConE Bug.%%%
It's now a ConE
, not an UnboundVarE
! My suspicion is that this is a consequence of RequiredTypeArguments
being implemented, although I'm unclear if this was an intentional change or not. (Note that I am not enabling RequiredTypeArguments
in this program.)
Either way, it leads to some confusing interactions in the singletons-th
library, which treats UnboundVarE
names differently from ConE
names. If we don't fix this issue on the GHC side, I'll need to devise a workaround in singletons-th
.