#4429: Ability to specify the namespace in mkName
---------------------------------+------------------------------------------
Reporter: reinerp | Owner:
Type: feature request | Status: new
Priority: normal | Milestone: 7.4.1
Component: Template Haskell | Version: 6.12.3
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by simonpj):
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.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4429#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs