Hi,
Yes, Michael's hack would do part of the trick, but I forgot to exemplify part of my question in the example code.
The whole idea is that I would like to be able to splice the generated Type into a TH quotation. Consider one of the world's most complicated identity functions:
{-# LANGUAGE TemplateHaskell #-}
import Data.Typeable
import Language.Haskell.Meta.Parse (parseType)
f :: Q Type -> Q Exp
f m = m >>= \t -> SigE (VarE 'id) (FunT t t)
liftT :: Typeable a => a -> Q Type
liftT x = either fail return $ parseType $ show $ typeOf x
-- separate files
splicef :: Typeable a => a -> a
splicef x = $(f (liftT x)) x
This code does not work because liftT depends on the value of x, exposing TH's state restrictions, but since we only need the type of x to evaluate liftT, we should be fine.
Thanks,
hugo