Metavariable leakage through Template Haskell reification
Using reify
on a variable defined in the same module results in metavariables reported to the user.
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.TH.Ppr
aNumber = 5
do VarI name1 t1 _ <- reify 'aNumber
runIO . print $ ppr_sig name1 t1
return []
Loading the code above code in GHCi produces the following output:
Main.aNumber :: p_0
What is p_0
? I would expect the reified type to match what :t +v
reports:
*Main> :t +v aNumber
aNumber :: Integer
In this particular case, disabling the monomorphism restriction fixes the issue:
{-# LANGUAGE NoMonomorphismRestriction #-}
Now the following reified type is printed:
Main.aNumber :: forall (p_0 :: *) . GHC.Num.Num p_0 => p_0
And it does match what :t +v
reports:
*Main> :set -fprint-explicit-foralls
*Main> :t +v aNumber
aNumber :: forall {p}. Num p => p
The same issue affects reifyType
and the regression test should test both reify
& reifyType
.
Edited by Vladislav Zavialov