
Hi, I'm starting to explore Template Haskell and I've got the following program: -- almost directly from "Template meta-programming in Haskell" paper module Duma.Template.Test ( Format(..) , printf ) where import Language.Haskell.TH data Format = D | S | L String printf :: [Format] -> ExpQ printf fs = gen fs [| "" |] gen :: [Format] -> ExpQ -> ExpQ gen [] x = x gen (D : xs) x = [| \n -> $(gen xs [| $x ++ show n |]) |] gen (S : xs) x = [| \s -> $(gen xs [| $x ++ s |] ) |] gen (L s : xs) x = gen xs [| $x ++ $(stringE s) |] module Main where import Duma.Template.Test import Language.Haskell.TH data Car = Car {_f :: Int} getInfo :: Q Info getInfo = reify (mkName "Car") main = do e <- runQ (printf [D,S,L "foo"]) putStrLn (pprint e) let x = $(printf [D,S,L "foo"]) 10 "hello" putStrLn x -- Crashes if I try to print out the info -- info <- runQ getInfo -- putStrLn (pprint info) _ <- getChar return () The example from the paper works fine with the few minor adjustements ie Expr --> ExpQ, lift --> stringE. However if I try and obtain the Info it compiles but then crashes at runtime (using ghc 6.4.2 on Windows). Any ideas? (Perhaps because the type doesn't exist - yet the first call to runQ (printf...) *does* work at runtime) Also, I'm puzzled by the type of reify, because the name "Car" above should surely be both a TyConI and a DataConI so how does this function decide which to return the info about? I expected an extra parameter to determine what namespace to look the name up in. BTW what I'm trying to do is write a TH function which adds a field to a data type and a corresponding instance method eg given: class Object a where getName :: a -> Unique foo :: a -> Int data Square = Square {_f :: Int} instance Object Square where foo = _f will modify the above code (or create new instance and new data type) to: data Square = Square {_name :: Unique, _f :: Int} instance Object Square where getName = _name foo = _f ie adding a bit of boilerplate to the data type and instance decl. Anyway any ideas about why reify doesn't distinguish between lookups of name-as-tycon vs name-as-datacon or why it crashes will be greatly appreciated ;-) Thanks, Brian. -- Logic empowers us and Love gives us purpose. Yet still phantoms restless for eras long past, congealed in the present in unthought forms, strive mightily unseen to destroy us. http://www.metamilk.com