Template Haskell crashes unexpectedly...
Bulat Ziganshin
bulat.ziganshin at gmail.com
Mon Aug 21 11:55:57 EDT 2006
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 at gmail.com
More information about the Glasgow-haskell-users
mailing list