how can I get template haskell macro-expanded code from inferStartState? (repeated post, now with subject)

(sorry, forgot the subject on my first post) In the following code which uses template haskell, how can I get back the macro-expanded code generated from $(inferStartState ''MyState) I *can* recover the macro-expanded code for $(cnst 1 "x") using a debugging technique bulat describes on his tutorial at http://www.haskell.org/bz/th3.htm You can see what's going on in the function debugTemplates below. I'm trying to do this actually, to better understand how HAppS deals with state. It's a bit opaque now since the example on the tutorial uses TH. I think I would understand it better if I had code that didn't depend on TH. (MyState is from the happs tutorial at http://www.haskell.org/haskellwiki/HAppS_tutorial ) thanks! thomas. {-# OPTIONS -fglasgow-exts -fth #-} module MyState where import HAppS import HAppS.Protocols.SimpleHTTP2 import Data.Monoid import Data.Typeable import Control.Monad.State (get, put) import Language.Haskell.TH import Language.Haskell.TH.Syntax data MyState = MySt { appVal :: Int } deriving (Read, Show, Typeable) instance Serialize MyState where encodeStringM = defaultEncodeStringM decodeStringM = defaultDecodeStringM instance Monoid MyState where mempty = MySt 0 mappend (MySt x) (MySt y) = MySt (x+y) -- in ghci... -fth, :m + -- ghci... :t (inferStartState ''MyState) :: (Quasi m) => m [Dec] $(inferStartState ''MyState) -- boilerplate that will eventually be SYB -- ghci... :t cnst 1 "x" :: (Monad m) => m Exp cnst n s = return (LamE (replicate n WildP) (LitE (StringL s))) dumpSplice splice = runQ splice >>= putStrLn . pprint debugTemplates = do dumpSplice (cnst 1 "x") dumpSplice (inferStartState ''MyState) {- *MyState> debugTemplates \_ -> "x" Template Haskell error: Can't do `reify' in the IO monad *** Exception: user error (Template Haskell failure) -} --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.

On 09/08/07, Thomas Hartman
(sorry, forgot the subject on my first post)
In the following code which uses template haskell, how can I get back the macro-expanded code generated from
$(inferStartState ''MyState)
I just recently used ghc -ddump-splices to debug this very same problem. It turns out to be due to overlapping instances - inferStartState generates a (from memory) specific StartStateEx instance, but actually theres a general StartState => StartStateEx, and also a general Monoid=>StartState instance, and thats why the error message mentions Monoid. I guess this teaches us the reason that overlapping instances are bad: ***They don't work across modules**** Another module can add an instance which wasn't visible when a first module was compiled, and the two modules end up using different instances than expected. I've been meaning to start trying to contribute to improving the HAppS documentation, since its been such a struggle to start learning it. So the question to the HAppS people is, where is the canonical place for this documentation, where should one work? Is it the wiki page above, or the stuff inside the HAppS repository? -- Brian_Brunswick____brian@ithil.org____Wit____Disclaimer____!Shortsig_rules!

I would say both.
The stuff under Examples in the repo should all run with 8.8. (I think
currently it doesn't.)
The stuff in the wiki should say what is 8.8, what is 8.4, and obviously
also give examples that work.
The advantage of the wiki is you can make a change that propogates to the
community without having commit priviliges for the repo.
at least, that's how I've been working. Just changing the wiki for now,
and maybe someday when I'm more confident about what I'm doing I'll ask
for a commit bit for the repo.
thomas.
"Brian Brunswick"
(sorry, forgot the subject on my first post)
In the following code which uses template haskell, how can I get back
the
macro-expanded code generated from
$(inferStartState ''MyState)
I just recently used ghc -ddump-splices to debug this very same problem. It turns out to be due to overlapping instances - inferStartState generates a (from memory) specific StartStateEx instance, but actually theres a general StartState => StartStateEx, and also a general Monoid=>StartState instance, and thats why the error message mentions Monoid. I guess this teaches us the reason that overlapping instances are bad: ***They don't work across modules**** Another module can add an instance which wasn't visible when a first module was compiled, and the two modules end up using different instances than expected. I've been meaning to start trying to contribute to improving the HAppS documentation, since its been such a struggle to start learning it. So the question to the HAppS people is, where is the canonical place for this documentation, where should one work? Is it the wiki page above, or the stuff inside the HAppS repository? -- Brian_Brunswick____brian@ithil.org____Wit____Disclaimer____!Shortsig_rules! --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.
participants (2)
-
Brian Brunswick
-
Thomas Hartman