Hi! I need to extract some type information from the syntax tree. Therefore I need to reify non-global names. Take the following example: module A where import Language.Haskell.TH logQ = runIO . putStrLn stringOfInfo (ClassI _) = "ClassI" stringOfInfo (ClassOpI name t _ _) = "ClassOpI " ++ show name ++ " :: " ++ show t stringOfInfo (TyConI _) = "TyConI" stringOfInfo (DataConI name t _ _) = "DataConI " ++ show name ++ " :: " ++ show t stringOfInfo (VarI name t _ _) = "VarI " ++ show name ++ " :: " ++ show t stringOfInfo (TyVarI name t) = "TyVarI " ++ show name ++ " = " ++ show t foo :: Q Exp -> Q [Dec] foo e' = do e <- e' case e of LetE _ (VarE name) -> do info <- reify name logQ (stringOfInfo info) return [] --- module Main where import A $(foo [| let f = \x -> x + 2 in f |]) main = return () --- What the example does is trying to reify 'f' in the expression let f = \x -> x + 2 in f When I now compile the example, I get the following output: $ ghc-cvs --make -fth B.hs Chasing modules from: B.hs Compiling A ( ./A.hs, ./A.o ) Compiling Main ( B.hs, B.o ) Loading package base ... linking ... done. Loading package haskell98 ... linking ... done. Loading package template-haskell ... linking ... done. B.hs:1:0: tcLookupGlobal: `f' is not in scope B.hs:1:0: Exception when trying to run compile-time code: Code: foo ([| let f = \ x -> ... in f |] where []) Exn: user error (IOEnv failure) I am using the development snapshot ghc-6.3.20040612. So my question is: Is it simply not possible to reify local definitions, is it a bug or is it not yet implemented? If it is possible in general to reify local definitions but just not implemented at the moment, do you have any schedule on when an implementation will be available? Thanks for helping! Stefan
participants (1)
-
Stefan Heimann