Undeliverable: Splicing types.. should this work?
Simon Peyton-Jones
simonpj at microsoft.com
Tue Feb 9 10:01:42 EST 2010
Robert
Interesting example. Here's your code:
createInstance' :: Q Type -> Q Dec
createInstance' t = liftM head [d|
instance Foo $t where
type FooType $t = String
|]
When TH sees a quotation, it *typechecks* it. So it tries to typecheck
instance Foo $t where
type FooType $t = String
During typechecking, it needs something to use as the type to which $t will expand. So it uses a fresh type variable -- but a different one each time. And this is what is biting you.
In general that's right. You would not expect it to work if you said
instance Foo $(t 19) where
type FooType $(t 19) = String
seeing that 't' is applied to the same argument each time. There no special case for plain variables.
So it's hardly a feature, but I can't see how to do just what you want.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Robert Greayer
| Sent: 25 January 2010 23:27
| To: glasgow-haskell-users at haskell.org
| Subject: Splicing types.. should this work?
|
| Now that type-splicing works in TH, and TH has type-family support, I
| was wondering if the following example should compile (with 6.12.1):
|
| > {-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, TypeFamilies,
| > FlexibleInstances, OverlappingInstances #-}
|
| > module Sample where
|
| > import Control.Monad
| > import Language.Haskell.TH
|
| > class Foo a where
| > type FooType a
|
| > createInstance :: Q Type -> Q Dec
|
| > createInstance t = instanceD (return [])
| > (conT ''Foo `appT` t) [
| > tySynInstD ''FooType [t] (conT ''String)
| > ]
|
| > createInstance' :: Q Type -> Q Dec
| > createInstance' t = liftM head [d|
| > instance Foo $t where
| > type FooType $t = String|]
|
| the function 'createInstance' compiles without a problem, but it's
| (near) equivalent
| written using TH quotations + splices fails with the error:
|
| Sample.lhs:22:10:
| Type indexes must match class instance head
| Found `t_aMn' but expected `t_aMl'
| In the associated type instance for `FooType'
| In the instance declaration for `Foo $t'
| In the Template Haskell quotation
| [d|
| instance Foo $t where
| type instance FooType $t = String |]
|
| The compiler seems to not be able to determine that the type spliced
| in the class instance head will match the type spliced in the type
| instance.
|
| The first version works fine for my purposes, but was curious whether
| the failure of the 2nd was a bug or a feature.
|
| Thanks,
| Rob
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list