parametrized data types and Template Haskell

Dear Cafe, Hope you all had a nice Christmas. I have been playing with generating method instances using Template Haskell but am a bit stuck now trying to generate an instance for a parametrized data type. I would like to generate the following:
instance (MyClass a) => MyClass (Tree a) where mymethod _ = "todo"
I defined a genMyClassInstance that is working fine for unparametrized data types, but clearly there is nothing here that inserts the '(MyClass a) =>' part here. My first question is: how should I instruct Template Haskell to insert the beforementioned code when appropriate?
genMyClassInstance :: Name -> Q [Dec] genMyClassInstance name = [d|instance MyClass $(conT name) where mymethod _ = "todo" |]
My second question is how to pass the Name of a parametrized data type? I tried the following, but GHC does not seem to like that: "Not in scope: type constructor or class `Tree a' Perhaps you meant `Tree'"
$(genMyInstance (mkName "Tree a"))
Thank you! Maarten Faddegon

Hello Maarten, You might also accept a string "Tree a" and then parse it as a Type by use of haskell-src-meta's parseType. Then you'll have to search through the Type data to get all the type variables, which might be tricky in the general case. Easier for you would be to require users to specify their type as: [t| forall a. Tree a |] This gives a data structure that looks like: ForallT [PlainTV a_16] [] (AppT (ConT Data.Tree.Tree) (VarT a_16)) Which I found by typing this into ghci: $([t| forall a. Tree a |] >>= stringE . show) The ForallT has all the pieces to generate the whole instance declaration: genMyClassInstance' :: Type -> Q Dec genMyClassInstance' (ForallT tvs _ ty) = instanceD (sequence [ classP ''MyClass [varT t] | PlainTV t <- tvs ]) [t| MyClass $(return ty) |] [funD 'myMethod [clause [wildP] (normalB [| "todo" |]) []] ] It often doesn't work to use [| |] quotes everywhere. So you have to use the functions/constructors in the Language.Haskell.TH module to make it yourself. That doesn't rule out being able to use those quotes as arguments to those functions (as you see above). Finally the use of genMyClassInstance' looks like: fmap return . genMyClassInstance' =<< [t| forall a. Tree a |] Which can be mostly hidden in another function to define which might be called "genMyClassInstance". Regards, Adam

Dear Cafe, Thanks to the kind help of Adam and Richard I now can generate instances for parametrized data types with Template Haskell. However, I still struggle adding class constraints to the type variables. I try to follow the derive_show example of Ian Lynagh but it seems some interfaces have changed since he wrote "Template Haskell: A Report From The Field". I generate MyClass constraints for a set of type variables with the following code:
genCxt :: [TyVarBndr] -> Q Cxt genCxt tvs = return [classp $ map (\v -> (tvname v)) tvs]
classp :: [Type] -> Pred classp = ClassP (mkName "TH_playground.MyClass")
tvname :: TyVarBndr -> Type tvname (PlainTV name ) = ConT name tvname (KindedTV name _) = ConT name
To be able to generate MyClass instances with:
genInstance :: Q Type -> Q [Dec] genInstance qt = do { t <- qt ; n <- case t of (ForallT tvs _ t') -> [t| MyClass $(return t') |] _ -> [t| MyClass $qt |] ; m <- genMethod qt ; c <- case t of (ForallT tvs _ t') -> genCxt tvs _ -> return [] ; return [InstanceD c n m] }
Up to here, everything type checks and I can build the module where I defined it. In a different module I try to generate an instance for MyData a:
data MyData a = MyCon a $(genInstance [t| forall a.MyData a |])
This however does not seems to go down well with the compiler. || Illegal type constructor or class name: `a' || When splicing a TH declaration: || instance TH_playground.MyClass a_0 => TH_playground.MyClass (Main.MyData a_0) || where myMethod (Main.MyCon x_1) = "todo" This error message confuses me because it seems to complain about the type variable a in the generate instance, but in the generated instance this variable is renamed to a_0. Also, when I copy the generated code from the error message the ghc is completely happy. Without the class constraints the generated instance type checks and compiles as well:
genCxt _ = return []
But I would like to apply myMethod on the fields in parametrized data types, which is not correct without the class constraints. Did I find a bug in ghc's Template Haskell implementation or am I doing something silly? Thanks, Maarten

On Mon, Dec 30, 2013 at 12:08 PM, Maarten Faddegon
Did I find a bug in ghc's Template Haskell implementation or am I doing something silly?
Hi Maarten, If you look at the definition of Name, you will see several NameFlavours. In your case your `a' has a NameU (unique). I think if you had the type variable names tagged with a NameS (simple?), ghc would accept your code. Somewhat related is a case where ghc accepts NameU as a NameS when no other variables in scope could conflict: x1 = [d| x = 1 |] is short for: x1 = return [ValD (VarP x_1627406778) (NormalB (LitE (IntegerL 1))) []] but when you splice x1, "x" is bound, instead of the unique, difficult-to-reference variable x_1627406778. Regards, Adam Vogt

Thanks for thinking with me Adam. It turned out the error message "Illegal type constructor or class name" was spot on, because I wrote:
tvname :: TyVarBndr -> Type tvname (PlainTV name ) = ConT name tvname (KindedTV name _) = ConT name
But should have written:
tvname :: TyVarBndr -> Type tvname (PlainTV name ) = VarT name tvname (KindedTV name _) = VarT name
Happy new year to all of you! Maarten

My experience with Template Haskell is that any non-trivial code generation (that is, anything more complicated than a simple substitution into a simple template) requires heavy use of the TH constructors, as Adam suggests. I tend to prefer using the non-monadic ones (like `InstanceD :: Cxt -> Type -> [Dec] -> Dec`) over the monadic ones (exported from Language.Haskell.TH.Lib and like `instanceD :: Q Cxt -> Q Type -> [Q Dec] -> Q Dec`), though you may find the opposite is true in your domain. Using these constructors, it is straightforward to specify a context, and you can use an empty list (the type `Cxt` is a synonym for `[Pred]`) for an empty context.
As for naming a parameterized type, just use the base name. So, `Tree a` would be (AppT (ConT (mkName "Tree") (VarT (mkName "a"))) assuming `a` is in scope somehow. You may also be interested in the naming quote syntax: in an expression, code like
'blah
expands out to a name for the term-level thing (i.e., function or variable) named `blah` that is in scope. Code like
''Tree
expands out to a name for the **type**-level thing (i.e., type, type function, class, etc.) name `Tree` that is in scope. Note that the line of code above has two single-quotes and no double-quotes. The number of quotes is necessary to disambiguate data constructors from types.
I hope this helps!
Richard
On Dec 26, 2013, at 6:36 AM, Maarten Faddegon
Dear Cafe,
Hope you all had a nice Christmas.
I have been playing with generating method instances using Template Haskell but am a bit stuck now trying to generate an instance for a parametrized data type.
I would like to generate the following:
instance (MyClass a) => MyClass (Tree a) where mymethod _ = "todo"
I defined a genMyClassInstance that is working fine for unparametrized data types, but clearly there is nothing here that inserts the '(MyClass a) =>' part here. My first question is: how should I instruct Template Haskell to insert the beforementioned code when appropriate?
genMyClassInstance :: Name -> Q [Dec] genMyClassInstance name = [d|instance MyClass $(conT name) where mymethod _ = "todo" |]
My second question is how to pass the Name of a parametrized data type? I tried the following, but GHC does not seem to like that: "Not in scope: type constructor or class `Tree a' Perhaps you meant `Tree'"
$(genMyInstance (mkName "Tree a"))
Thank you!
Maarten Faddegon _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
adam vogt
-
Maarten Faddegon
-
Richard Eisenberg