Template Haskell crashes unexpectedly...

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

Hello Brian,
[snip] getInfo :: Q Info getInfo = reify (mkName "Car") [snip] -- Crashes if I try to print out the info -- info <- runQ getInfo -- putStrLn (pprint info) [snip]
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)
I seem to remember that 'reify' cannot be run in the IO monad. IIRC ghci gives a nice error message saying this, so perhaps you can try to execute 'main' from within ghci to corroborate my suspicion.
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.
The preferred way to refer to names that are in scope is by using the quotation mechanism: 'getName is the name of the function 'getName' ''Object is the name of the type 'Object' This also makes the distinction you rightly wanted. Greetings, Arie -- Mr. Pelican Shit may be Willy. ^ /e\ ---

Hello Arie, Monday, August 21, 2006, 7:08:31 PM, you wrote:
getInfo :: Q Info getInfo = reify (mkName "Car")
-- Crashes if I try to print out the info -- info <- runQ getInfo
I seem to remember that 'reify' cannot be run in the IO monad.
oh, yes! runQ is just a way to test simple things, it's not a full-featured Q monad emulator. reify should be called at compile-time to get access to identifiers table and it crashes just because no exception handler was installed this is the appropriate part of TH library: class Monad m => Quasi m where qNewName :: String -> m Name qReport :: Bool -> String -> m () qRecover :: m a -> m a -> m a qReify :: Name -> m Info qCurrentModule :: m String qRunIO :: IO a -> m a Quasi class covers all operations of Q monad. It has two implementations: instance Quasi Q where qNewName = newName qReport = report qRecover = recover qReify = reify qCurrentModule = currentModule qRunIO = runIO this instance work for code generated at compile-time by $(...) splices and this instance used when you run computations in Q monad inside your program, at run-time, using runQ operation: instance Quasi IO where qNewName s = do { n <- readIORef counter ; writeIORef counter (n+1) ; return (mkNameU s n) } qReport True msg = hPutStrLn stderr ("Template Haskell error: " ++ msg) qReport False msg = hPutStrLn stderr ("Template Haskell error: " ++ msg) qReify v = badIO "reify" qCurrentModule = badIO "currentModule" qRecover a b = badIO "recover" -- Maybe we could fix this? qRunIO m = m badIO :: String -> IO a badIO op = do { qReport True ("Can't do `" ++ op ++ "' in the IO monad") ; fail "Template Haskell failure" } as you can see, it don't supports reification, recovery and information about currently compiled module just because there is no such information when program runs. and of course, you can't add new fields or new functions at run-time. isntead typical technique is: $(transform [d| data D = X {f::Int, g::String} |] ) where 'transform' parses declaration passed and generates something like this data D = X {unique::Int, f::Int, g::String} of course, you can also use reification, it's a matter of taste -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
as you can see, it don't supports reification, recovery and information about currently compiled module just because there is no such information when program runs. and of course, you can't add new fields or new functions at run-time. isntead typical technique is:
$(transform [d| data D = X {f::Int, g::String} |] )
where 'transform' parses declaration passed and generates something like this
data D = X {unique::Int, f::Int, g::String}
Thanks - by coincidence I was also coming to this conclusion after reading the tutorial because it avoids the nusiance of being left with unwanted data/instance decls in the module (and the need to rename everything when generating the extended data/instance decls to avoid conflicts with field names etc). The solution seems to be something like: $(extend_data [d| data D = X {f::Int, g::String} |]) $(extend_instance [d| instance Obj D where ... |]) for some fairly trivial extend functions which will just add the AST for the extra field and method to the AST of the data and instance respectively, and by the idea in http://www.haskell.org/bz/th3.htm I can just use ghci to get the extra syntax trees to copy and paste into my extend functions. Still it's too late tonight to do any more programming so I'll have to leave this for tomorrow... ! ;-) Best regards, 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

Hello Brian, Tuesday, August 22, 2006, 1:16:08 AM, you wrote:
The solution seems to be something like:
$(extend_data [d| data D = X {f::Int, g::String} |])
$(extend_instance [d| instance Obj D where ... |])
or just $(extend_data [d| data D = X {f::Int, g::String} instance Obj D where ... |]) because [d| ... |] can include multiple declarations -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Arie Peterson wrote:
I seem to remember that 'reify' cannot be run in the IO monad. IIRC ghci gives a nice error message saying this, so perhaps you can try to execute 'main' from within ghci to corroborate my suspicion.
Yes you're right - ghci gives the error: "Can't do `reify' in the IO monad"
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.
The preferred way to refer to names that are in scope is by using the quotation mechanism:
'getName is the name of the function 'getName' ''Object is the name of the type 'Object'
This also makes the distinction you rightly wanted.
Thanks, Brian.

Hello Brian, Monday, August 21, 2006, 6:34:06 PM, you wrote:
-- almost directly from "Template meta-programming in Haskell" paper
i should warn you that some TH details was changed in 6.4. these changes described in second TH paper and afair, reifying is among them look at www.haskell.org/bz/thdoc.htm, "reification" section and www.haskell.org/bz/th3.htm i hope these docs, although still unfinished, may help you -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Brian,
Monday, August 21, 2006, 6:34:06 PM, you wrote:
-- almost directly from "Template meta-programming in Haskell" paper
i should warn you that some TH details was changed in 6.4. these changes described in second TH paper and afair, reifying is among them
look at www.haskell.org/bz/thdoc.htm, "reification" section and www.haskell.org/bz/th3.htm
i hope these docs, although still unfinished, may help you
Yes these docs are *brilliant* ! Exactly what I need to get an understanding of TH. Thanks a lot, Brian.
participants (3)
-
Arie Peterson
-
Brian Hulley
-
Bulat Ziganshin