`tc_infer_hs_type` doesn't add module finalisers
Summary
I investigated #23639 and found that tc_hs_type
calls addModFinalizersWithLclEnv
on untyped top-level splices, but tc_infer_hs_type
does not. I found this behavior to be strange and is likely a bug. After some investigation, I came up with a test case that exhibits the problem. Luckily, the fix for this bug should be a one line change.
Steps to reproduce
{-# LANGUAGE TemplateHaskell #-}
module T where
import Language.Haskell.TH.Syntax (addModFinalizer, runIO)
import GHC.Types (Type)
type Proxy :: forall a. a -> Type
data Proxy a = MkProxy
check :: ($(addModFinalizer (runIO (putStrLn "check")) >>
[t| Proxy |]) :: Type -> Type) Int -- There is kind signature, we are in check mode
check = MkProxy
infer :: ($(addModFinalizer (runIO (putStrLn "infer")) >>
[t| Proxy |]) ) Int -- no kind signature, inference mode is enabled
infer = MkProxy
Attempt to compile this code will result in the following stdout:
$ ghc T.hs -fforce-recomp
[1 of 1] Compiling T ( T.hs, T.o )
check
Expected behavior
$ ghc T.hs -fforce-recomp
[1 of 1] Compiling T ( T.hs, T.o )
check
infer
Environment
- GHC version used: master
Edited by Andrei Borzenkov