
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