[Template-haskell] Reification of local names

Simon Peyton-Jones simonpj at microsoft.com
Mon Jun 21 12:52:04 EDT 2004


You're trying to use reify for something it's not designed for.

reify looks something up in the type environment, *at the point where
that Q computation was spliced in*.  So if I say

foo :: Q Info
foo = reify (mkName "wog")

then the reify will look up "wog" wherever I say $foo.  Not at the point
where foo is defined.

In this case, you're going to look up the name in  your syntax tree, but
you'll look it up in the type environment where $foo is spliced in --
which is the top level of module A.


The "right place" to find the type info for a given syntax tree is in
the syntax tree.  The type checker has processed your fragment 
	[| let f = \x -> x + 2 in f |]
You just want to see the types.   Currently there is no way to do that,
but people often ask for it.

One idea: add (Maybe Type) fields to many TH syntax forms, where the
type checker can record types.  That's simple and direct. 

A general question to TH aficionados: would this be useful?  Remember
that the type may not be fully precise, because it's the result of
type-checking an as-yet-unspliced fragment.

Simon

| -----Original Message-----
| From: template-haskell-bounces at haskell.org
[mailto:template-haskell-bounces at haskell.org] On
| Behalf Of Stefan Heimann
| Sent: 17 June 2004 15:46
| To: template-haskell at haskell.org
| Subject: [Template-haskell] Reification of local names
| 
| 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
| _______________________________________________
| template-haskell mailing list
| template-haskell at haskell.org
| http://www.haskell.org/mailman/listinfo/template-haskell


More information about the template-haskell mailing list