[Template-haskell] mysterious type inference problem in splice
Daniel Brown
brownd at cse.ogi.edu
Fri Apr 16 21:57:32 EDT 2004
I'm using Template Haskell for the first time, trying to do some code
manipulation, and I'm getting some error messages I don't understand.
In the code below, idwrap[01] behave as expected, but idwrap2 does not
work the same way:
*Q> $(idwrap0 i1)
1
*Q> $(idwrap1 i1)
1
*Q> $(idwrap2 i1)
<interactive>:1:
No instance for (Num ExpQ)
arising from the literal `1' at <interactive>:1
In the first argument of `idexp', namely `1'
In the definition of `it': it = $[splice](idwrap2 i1)
What's going on here? Why does the system want to prove (Num ExpQ)? (I
should add that I'm also new to GHC, though I have used Hugs a fair
amount.)
-- Dan.
------------------------------------------------------------------------
module Q where
import Language.Haskell.THSyntax
idq = id
idexp = id :: ExpQ -> ExpQ
idwrap0 e = appE (varE "GHC.Base:id") e
idwrap1 e = appE (varE "Q:idq") e
idwrap2 e = appE (varE "Q:idexp") e
i1 = litE (integerL 1)
More information about the template-haskell
mailing list