
Hmm, did you try to compile that code? FunT doesn't exist. The
definition of f should be:
f :: Q Type -> Q Exp
f m = m >>= \t -> return $ SigE (VarE 'id) (AppT (AppT ArrowT t) t)
Or, better yet:
f = fmap (\t -> SigE (VarE 'id) (AppT (AppT ArrowT t) t))
Yes, something like splicef is impossible, and this is exactly the
kind of situation the stage restriction prevents. Consider how a
usage of 'splicef' would need to work. Since the type is only known
when compiling an invocation of it, this is also when code generation
would need to happen. If it's used polymorphically within a function,
then *that* function would also need to be recompiled for each of its
invocations. In other words, it would need to be like C++ templates,
rather than Haskell's normal polymorphic functions.
Here's the best thing I can think of that might be useful (using typed
expressions, because why not!). What's your usecase?
{-# LANGUAGE TemplateHaskell #-}
module A where
import Data.Typeable
import Language.Haskell.Meta.Parse (parseType)
import Language.Haskell.TH
liftT :: Typeable a => a -> Q Type
liftT x = either fail return $ parseType $ show $ typeOf x
splicef :: Typeable a => a -> Q (TExp (a -> a))
splicef x = do
ty <- liftT x
[e|| id :: ty -> ty ||]
someValue :: [(Int, Int)]
someValue = []
{-# LANGUAGE TemplateHaskell #-}
module B where
import A
main = $$(splicef someValue) someValue
On Thu, Oct 16, 2014 at 5:52 AM, Hugo Pacheco
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) import Language.Haskell.TH
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
On Thu, Oct 16, 2014 at 1:22 AM, Michael Sloan
wrote: 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
wrote: 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
-- www.cs.cornell.edu/~hpacheco