GHC desugarer error with OPAQUE + TempateHaskell
This program will crash when compiled with GHC 9.4 or HEAD:
{-# LANGUAGE TemplateHaskell #-}
module Main where
main :: IO ()
main = print
$([| let f :: Int -> Int
f x = x + 1
{-# OPAQUE f #-}
in f 41
|])
$ ~/Software/ghc-9.3.20220413/bin/ghc Bug.hs -fforce-recomp
[1 of 2] Compiling Main ( Bug.hs, Bug.o, Bug.dyn_o )
GHC error in desugarer lookup in Main:
Can't find interface-file declaration for data constructor Opaque
Probable cause: bug in .hi-boot file, or inconsistent .hi file
Use -ddump-if-trace to get an idea of which file caused the error
This program works if the intervening Template Haskell splice is removed, however:
module Main where
main :: IO ()
main = print $
let f :: Int -> Int
f x = x + 1
{-# OPAQUE f #-}
in f 41
$ ~/Software/ghc-9.3.20220413/bin/ghc Bug.hs -fforce-recomp && ./Bug
[1 of 2] Compiling Main ( Bug.hs, Bug.o )
[2 of 2] Linking Bug
42