"Template Haskell and higher order meta programming."

I generally have 2 questions. I am writing some functions to derive typeclass instances with a package called derive. I just want to get rid of using Derivation type with a stupid reason. I want use just Name type. How can I defined a function with type derivings :: Name -> Name -> Q [Dec] by using function derive :: Derivation -> Name -> Q [Dec] so that user can just write derivings ''Eq ''D instead of derive makeEq ''D?
{-# LANGUAGE TemplateHaskell #-}
import Data.DeriveTH -- in derive package import Language.Haskell.TH import qualified Language.Haskell.TH.Syntax as S data D = D derivings :: Name -> String -> Q Exp derivings cla typ = do let makeClassName = mkName $ "make" ++ nameBase cla a <- [| derive makeClassName (mkName typ) |] return a
instance S.Lift Name where lift x = varE x
Main> :t derivings ''Eq "D" derivings ''Eq "D" :: Q Exp Main> :t $(derivings ''Eq "D") $(derivings ''Eq "D") :: Q [Dec] There is no problem to quote twice in other file in order to get the declaration. Maybe it should called second order meta programming. But the following has problems:
derivings'' :: Name -> Name -> Q Exp derivings'' cla typ = do let makeClassName = mkName $ "make" ++ nameBase cla a <- [| derive makeClassName typ |] return a
Main> :t derivings'' derivings'' :: Name -> Name -> Q Exp Main> :t derivings'' ''Eq ''D derivings'' ''Eq ''D :: Q Exp Main> :t $(derivings'' ''Eq ''D) <interactive>:1:3: Illegal variable name: ‘D’ When splicing a TH expression: Data.DeriveTH.derive makeEq (Language.Haskell.TH.Syntax.mkName Main.D) In the splice: $(derivings'' ''Eq ''D) In the first case I used String, it works. however, it is not workiing if I use D with a Name type. Cannot figure it out. My second question is that if my return type is Q [Exp] while the [Exp] can be further expanded into [Dec]. How can I do it to expand [Exp] into [Dec]? Do we have a function for $ in $(thcode_with_Q_Exp) so that I do not need to splice each Exp value? Best wishes Song
participants (1)
-
Song Zhang