If we do reify (mkName "Foo") then we get the information about "Foo the type", and not about "Foo the constructor".
(This is problematic, say, for a quasiquoter
[qq| ... Foo ... |]
because the quasiquoter is forced to use mkName "Foo" as the Name for reify -- the forms 'Foo and ''Foo are unavailable to it.)
I would like a way around this problem. It seems like it would be enough to communicate the namespace to mkName, so that the ambiguity no longer exists.
I think mkName is the wrong thing for you here. Fundamentally, you want to get the TH.Name of the data type called "Foo" that is currently in scope, yes? You could give that Name to reify, or you could use it in a type. Suppose we had
lookupType :: String -> Q Name lookupValue :: String -> Q Name
that were like mkName except that (a) they are monadic, and (a) they expect the string to be in scope. The would be the precise monadic equivalents of 'Foo and ''Foo. Would that do the job?
Here's an alternative signature, for which the above could be wrappers
lookupName :: TH.NameSpace -> String -> Q Name
And if the String looks like "M.x" then it should be treated as a qualified name, just as in source code.
Finally, the environment in which the name is looked up is the environment at splice point: it reads the environment captured in the monad. So for example:
module M where muggle :: Int muggle = 3 -- This binding is ignored foo :: Q Exp foo = do { n <- lookupName VarName "muggle" ; return (AppE (VarE 'negate) (VarE n) ) } bar :: Q Exp bar = [| \muggle -> muggle + $foo |]-----------module N where import M muggle :: Int muggle = 5 test1 = $foo -- Expands to (negate muggle) test2 = $bar -- Expands to (\muggle' -> muggle' + muggle)
The splice $foo will run the code for foo, which consults N's environment (not M's!), to get the Name for N.muggle. The net result is very similar as if you'd used mkName "muggle", except that it still works if there is an intervening binding that accidentally has the same name, as in test. Subtle stuff.
The reason I ask this is that it should be possible for ordinary Template Haskell users to implement the "totally fresh" semantics I was looking for in #5375 (closed) using lookupName, as follows:
generate a long string at random
look it up with lookupName. If the lookup fails, then we have a fresh name, otherwise loop.
Yes of course. I was thinking that the lookup would fail, and you could catch the exception with qRecover. But perhaps a Maybe is better because it signals more explicitly that the lookup might fail.
I'm about to commit a patch implementing this change. In the end I did not give a NameSpace argument because NameSpace is currently an opaque type. Really what we want is just to say "type namspace" or "value namespace", so I ended up with two functions
Both end up mapping to the same method of the Quasi class
class Quasi m where ... lookupName :: Bool -> String -> m (Maybe Name) ...
The Bool is True for the type namespace, and False for values. Not beautiful, but most users will use the lookupTypeName and lookupValueName interfaces.
I've attached a patch with regression tests for this and #5406 (closed).
I'd appreciate it if you had a look at the shadowing tests in TH_lookupName.hs. I'm not sure if the current behaviour is correct.
My specific question is what should this do:
{-# LANGUAGE TemplateHaskell #-}import Language.Haskell.THf = "global"main = print [ $( [| let f = "local" in $(do { Just n <- lookupValueName "f"; varE n }) |] ), $( [| let f = "local" in $(varE 'f) |] ), let f = "local" in $(do {Just n <- lookupValueName "f"; varE n }), let f = "local" in $(varE 'f) ]
This currently prints ["global","local","local","local"]. Should the first two really give different results?
This currently prints ["global","local","local","local"]. Should the first two really give different results?
Well, yes, that's the current deal. All reify operations consult the environment at the point of the enclosing top-level splice. For a more extreme example, consider
module M where funny :: Q Exp funny = do { Just n <- lookupValueName "f"; varE n } f :: Int f = 3module Top where import M me = $(funny) f :: Bool f = True
Here the lookupValueName consults the environment at the top-level splice, which in this case in in module Top, not in M. So the expanded code will bind to Top.f not to M.f.
Doing anything else would be hard, and this is consistent with what happens for all other reification.
None of this is documented. If I could ask one last favour, would you feel able to expand (or re-structure) the user manual section about Template Haskell http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.html? This could range from no-op, through at least documenting the key operations (like reify).
I'm wondering about the Maybe Dec field in the VarI constructor of Info. Is it ever a Just? My understanding is that reify should return a Just when the RHS is available, but I can't get this to happen. For example, this code:
f = 0$( do { inf <- reify (mkName "f"); runIO (print inf); [d| |] })
prints
VarI ReifyVar.f (VarT a_1946157057) Nothing (Fixity 9 InfixL)
I've got a similar question, this time about TyVarI. Consider this example:
{-# LANGUAGE TemplateHaskell, ScopedTypeVariables, TypeFamilies #-}module ReifyTyVar whereimport Language.Haskell.THf :: forall a. a -> af x = $( do { inf <- reify (mkName "a"); runIO (print inf); [| x |] })g :: forall b. (b ~ Int) => b -> bg x = $( do { inf <- reify (mkName "b"); runIO (print inf); [| x |] })
In both of these cases, the Type field of TyVarI is just a VarT of the Name field.
Are there any examples where this is not the case? I thought that g might be such an example, because the type coercion b ~ Int is available, but apparently not.
It looks as if I never implemented the Just dec part of VarI! It's not straightforward
We don't have source-code defintions for imported Ids. They've all been converted to Core, and even the Core may not be available if the defn is big.
In principle we do have source code for local-defined Ids, but at the moment we don't carry around a mapping from Ids to their definitions.
So currently you always get Nothing. I don't want to change that until it becomes a pressing need for someone, but you are dead right that it should be documented. Just say "always Nohthing" for now!
For TyVarI, the situation is this: there is a lexically-scoped, source-code type variable name that maps to an internal type variable, of the sort that appears in types. In principle, you could imagine a system in which a lexically scoped type varaible maps to a type not a type variable:
f :: Int -> Intf (x::a) = 3::a
Here 'a' maps to 'Int'. Now in fact GHC's design insists that source-language type varaibles map to internal variables, but I didn't want to bake that in too much. And I'm not certain that I guarantee they map to distinct type variables.
This is all a bit confusing. I think a better design would indeed identify these internal and external type variables -- the distinction is confusing. But it's another swamp I don't want to enter just yet.
I just attached the progress I've made so far (as a patch, and also as prebuilt html files), and I would appreciate some feedback.
I reordered a lot of the exports in Language.Haskell.TH and Language.Haskell.TH.Syntax to create an order which made more sense to me, and to break things up into sections.
My patch actually includes a few small changes to the API as well:
I added functions reportError = report True and reportWarning = report False, which I think are present a better API than report :: Bool -> String -> Q ()
I added some type synonyms, ParentName, Arity, Unlifted for Info type
I exported unboxedTupleTypeName and unboxedTupleDataName from Language.Haskell.TH, since it seems to have simply been an accident that they were omitted.
There were a few other changes I refrained from making, but have described at #5469 (closed).
I guess the main thing I'd like confirmation on is whether it's okay for me to make small API changes as I've been doing so far, or should I leave these out and just make documentation changes for now?
Author: Simon Peyton Jones <>Date: Mon Jul 16 17:42:49 2012 +0100 Add documentation for Template Haskell functions Thanks to Reiner Pope for doing this