
Here's a hacky solution to this, using haskell-src-meta to parse the type:
{-# LANGUAGE TemplateHaskell #-}
import Data.Typeable
import Language.Haskell.Meta.Parse (parseType)
import Language.Haskell.TH
liftT :: Typeable a => a -> Type
liftT x = either error id $ parseType $ show $ typeOf x
This doesn't handle qualification properly, as the instance of Show
for TypeRep doesn't qualify names. A proper solution would involve
directly writing a (TypeRep -> Type) function.
On Wed, Oct 15, 2014 at 9:06 PM, Hugo Pacheco
Hi list,
I am 99.9% sure that this is currently not possible, but I might as well ask:
Is there a way to lift type variables into Template Haskell type splices?
What I had in mind would be something like this (erroneous) code:
liftT :: a -> Q Type liftT (_::a) = [t| $a |]
I have no idea how hard it would be to implement such a feature, or if it is remotely doable. Naively, it seems to me that TH would have to delay evaluating the splice until the type variable is fully expanded, but all the necessary information would still be available at some point during compilation.
Cheers, hugo
-- www.cs.cornell.edu/~hpacheco
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe