[Template-haskell] mysterious type inference problem in splice

Simon Peyton-Jones simonpj at microsoft.com
Tue Apr 20 14:17:38 EDT 2004


Consider what 
	$(idwrap2 i1) expands to.  

It's just as if you wrote

	i1 = [| 1 |]

	$( [| idexp $i1 |] )

Inlining i1 gives

	$( [| idexp 1 |] )

and indeed idexp expects an ExpQ (think syntax tree) whereas 1 is
plainly just a number.

In general you'd be much better off using the quotation notation unless
you absolutely have to use appE and friends, for reasons described in
the paper.
	http://research.microsoft.com/%7Esimonpj/papers/meta-haskell

Simon

| -----Original Message-----
| From: template-haskell-bounces at haskell.org
[mailto:template-haskell-bounces at haskell.org] On
| Behalf Of Daniel Brown
| Sent: 17 April 2004 04:58
| To: template-haskell at haskell.org
| Subject: [Template-haskell] mysterious type inference problem in
splice
| 
| 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)
| 
| _______________________________________________
| template-haskell mailing list
| template-haskell at haskell.org
| http://www.haskell.org/mailman/listinfo/template-haskell


More information about the template-haskell mailing list