splices in type signatures
Hello, Is it possible to have a TH splice in a type signature? It seems to generate a parse error, but I thought there might be another syntax that I'm not aware of. Thanks, Frederik -- http://ofb.net/~frederik/
Hello Frederik, Wednesday, June 14, 2006, 9:46:33 PM, you wrote:
Is it possible to have a TH splice in a type signature? It seems to generate a parse error, but I thought there might be another syntax that I'm not aware of. Thanks,
the following straightforward code don't work f :: $( ''Int ) f = 1 - i think because ghc still has serious limitations on the places where splicing can occur but you can emulate such behavior, it just needs more work. look at the following program: {-# OPTIONS_GHC -cpp -fth -fglasgow-exts #-} $([d| f :: Int f = 1 |]) main = print f it compiles and works ok. [d|...|] here generates list containing two declaration statements, where first matches to the "SigD Name Type" alternative in Dec type. as the result, you can substitute this Type with what you want (Integer here): {-# OPTIONS_GHC -cpp -fth -fglasgow-exts #-} module Th1 where import Language.Haskell.TH generate = do [sig,def] <- [d| f :: Int f = 10 |] let (SigD name _) = sig return [SigD name (ConT ''Integer), def] and then use it: {-# OPTIONS_GHC -cpp -fth -fglasgow-exts #-} import Th1 $(generate) main = print (f^40) i've also attached example of using this technique to deriving Show instances -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
It was my plan to allow this, so you could write f :: Int -> $(h x) but it turned out to be awkward to implement it, and I never did. So far anyway. Simon | -----Original Message----- | From: template-haskell-bounces@haskell.org [mailto:template-haskell-bounces@haskell.org] On Behalf | Of Frederik Eaton | Sent: 14 June 2006 18:47 | To: template-haskell@haskell.org | Subject: [Template-haskell] splices in type signatures | | Hello, | | Is it possible to have a TH splice in a type signature? It seems to | generate a parse error, but I thought there might be another syntax | that I'm not aware of. Thanks, | | Frederik | | -- | http://ofb.net/~frederik/ | _______________________________________________ | template-haskell mailing list | template-haskell@haskell.org | http://www.haskell.org/mailman/listinfo/template-haskell
participants (3)
-
Bulat Ziganshin -
Frederik Eaton -
Simon Peyton-Jones