[Template-haskell] Reification of top level variables - was: Re: Problem with Labelled Fields
Eric Offermann
eric.offermann@gmx.net
Fri, 27 Jun 2003 11:43:21 +0200 (MEST)
> What you will actually
> get is the code for applying "c_succ" to lift c (it is lifted as it is
> an argument to the function). However, lifting c needs to use this
> instance again so loops.
>
> Ian
Ian, thanks a lot for pointing that out. This leads me to the following
modification:
{- spliceC.hs -}
module spliceC where
import Language.Haskell.THSyntax
data C a = C
{c_succ :: a -> a
,c_pred :: a -> a
}
instance Lift (C a) where
lift c =
recCon "C"
[fieldExp "c_succ" [| c_succ $(var "sampleC") |]
,fieldExp "c_pred" [| c_pred $(var "sampleC") |]
]
c_succS :: C a -> ExpQ
c_succS c = [| \ a -> c_succ c a |]
sampleC :: C Int
sampleC = C
{c_succ = \ n -> n + 1
,c_pred = \ n -> n - 1
}
Thus, the possibility of using a "reifyVar c :: Q String" in the instance of
lift c yielding the original name of c would be useful to keep the instance
decleration generic. Any hint on implementing that?
Thanks,
Eric
--
+++ GMX - Mail, Messaging & more http://www.gmx.net +++
Bitte lächeln! Fotogalerie online mit GMX ohne eigene Homepage!