Core Lint error with typed Template Haskell (The type variable ... is out of scope)
The parsley-0.1.0.1
Hackage library fails to compile with -dcore-lint
. Here is a minimized version of the failing code:
{-# LANGUAGE TemplateHaskell #-}
module Bug where
import Control.Monad.ST
import Language.Haskell.TH
f :: Code Q Char
f = [|| runST $$([|| pure 'a' ||]) ||]
$ /opt/ghc/9.0.1/bin/ghc Bug.hs -dcore-lint
[1 of 1] Compiling Bug ( Bug.hs, Bug.o, Bug.dyn_o )
*** Core Lint errors : in result of Desugar (before optimization) ***
<no location info>: warning:
The type variable @s_a20Z[sk:1] is out of scope
In the type of a binder: $dApplicative_a218
In the type ‘Applicative (ST s_a20Z[sk:1])’
Substitution: [TCvSubst
In scope: InScope {}
Type env: []
Co env: []]
*** Offending Program ***
Rec {
$dQuote_a211 :: Quote Q
[LclId]
$dQuote_a211 = $dQuote_a20R
$dQuote_a20R :: Quote Q
[LclId]
$dQuote_a20R = $fQuoteQ
$dApplicative_a218 :: Applicative (ST s_a20Z[sk:1])
[LclId]
$dApplicative_a218 = $fApplicativeST @s_a20Z[sk:1]
$trModule :: Module
[LclIdX]
$trModule = Module (TrNameS "main"#) (TrNameS "Bug"#)
f :: Code Q Char
[LclIdX]
f = unsafeCodeCoerce
@'LiftedRep
@Char
@Q
$dQuote_a20R
(appE
@Q
$dQuote_a20R
(varE
@Q
$dQuote_a20R
(mkNameG_v
(unpackCString# "base"#)
(unpackCString# "GHC.ST"#)
(unpackCString# "runST"#)))
(unTypeCode
@'LiftedRep
@(ST s_a20Z[sk:1] Char)
@Q
$dQuote_a20R
(unsafeCodeCoerce
@'LiftedRep
@(ST s_a20Z[sk:1] Char)
@Q
$dQuote_a211
(appE
@Q
$dQuote_a211
(varE
@Q
$dQuote_a211
(mkNameG_v
(unpackCString# "base"#)
(unpackCString# "GHC.Base"#)
(unpackCString# "pure"#)))
(litE @Q $dQuote_a211 (charL (C# 'a'#)))))))
end Rec }
*** End of Offense ***
<no location info>: error:
Compilation had errors