[GHC] #9946: Expose the source location of template-haskell Names

#9946: Expose the source location of template-haskell Names -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature | Status: new request | Milestone: Priority: low | Version: 7.11 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I've often wanted to know where a particular `Name` is defined (specifically the filepath), but as far as I can tell, template-haskell doesn't currently support this. It'd be really nice to have a function {{{#!hs nameLoc :: Name -> Loc }}} to expose the definition site of the `Name`. I think this should be fairly straightforward to add since GHC carries the definition site around with its `Name`s, but I've never looked at the TH internals. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9946 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9946: Expose the source location of template-haskell Names -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): What is the specification? Exactly what location would you expect to get? Examples would be a good start. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9946#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9946: Expose the source location of template-haskell Names -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Spec: Add a single function {{{ nameSrcLoc :: TH.Name -> GHC.SrcLoc.SrcLoc }}} using the upcoming `SrcLoc` type from [https://phabricator.haskell.org/D578 D578], which returns the span of the whole definition, e.g. {{{ module A where head :: [a] -> a head [] = undefined head (x:_) = x }}} {{{ module B where loc = nameLoc 'A.head -- loc == A.hs:3:1-5:15 }}} This provides maximal information, and my intuition is that it might be easier for clients to narrow the span (e.g. to the first equation) if needed than to widen it. But, as above, I've only ever needed the filepath in practice, so I'm very open to convincing that a different span would be more useful. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9946#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9946: Expose the source location of template-haskell Names -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Actually, including the type signature doesn't seem feasible (or at least useful), given that {{{ foo :: Int -> Int bar :: Int -> Int foo = ... bar = ... }}} is perfectly valid. So let me amend my example [comment:2 above] to {{{ loc = nameLoc 'A.head -- loc == A.hs:4:1-5:15 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9946#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9946: Expose the source location of template-haskell Names -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): An example is good, and I encouraged you to start with examples. But ultimately we need a complete specification that says what happens for every `Name`. There are lots of ways to generate a `Name` in TH, and you only give one. How about {{{ f :: Q Exp -> Q Exp f qe = do { Var x <- qe ; print (nameLoc x) ; [| blah |] } }}} For example I might call f with `f [| x |]`, or `f [| \x -> x |]`. Or you can use `newName` or `mkName` to create a `Name`. What locations would they have? Look at `data Name` and `NameFlavour` in `Language.Haskell.TH`. I guess that you ''might'' reasonably expect a location for a `NameG` and perhaps a `NameL`. But it's not clear that `nameLoc :: Name -> Maybe SrcLoc` will be useful to you. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9946#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9946: Expose the source location of template-haskell Names -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Oh of course, I forgot about binding `Name`s inside the `Q` Monad.. That goes to show how much I actually use TH. I think we can break the `Name`s into three categories: 1. Bound outside of TH (`NameL` and `NameS`): These are probably the easiest to handle, following my example [comment:3 above]. 2. Bound inside TH, uncapturable (`NameU`): This one also seems pretty straightforward since we know precisely where the `Name` was created, the call-site of `newName` (or `qNewName`). At the moment it's not easy to reflect that location to the running TH code, but the upcoming implicit-params call-stacks would work nicely here (I think). We'd change the types of `newName` and `qNewName` to {{{ newName :: ?loc :: CallStack => String -> Q Name qNewName :: (?loc :: CallStack, Quasi m) => String -> m Name }}} I'm not convinced this location would ever actually be //useful//, but it's a sensible answer and I think we can generate it. 3. Bound inside TH, capturable (`NameS` and `NameQ`): The desired behavior here would be to produce the `SrcLoc` corresponding to the definition of whatever `GHC.Name` the `TH.Name` resolves to, but I'm not sure how to do that yet. Somewhere inside GHC (I suspect wherever the splices are compiled and run) this dynamic resolution must be performed already. So //ideally//, we would just hook into that resolution process. This one seems by far the most difficult though. I'd also be open to returning a `Maybe SrcLoc`, which would only be defined in case (1), as that's good enough for my personal use. But it would sure be nicer to always return a sensible `SrcLoc`. EDIT: I just remembered that there's a function `CoreMonad.thNameToGhcName` that might be useful, though it might also attach an `UnhelpfulSrcSpan` to the `GHC.Name`. I'll experiment with it a bit and report back. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9946#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9946: Expose the source location of template-haskell Names -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): There is, unfortunately, a subcase in (1) that I forgot above, namely wired-in `Name`s. We can't ever hope to produce a useful `SrcLoc` from `nameSrcLoc '[]`. This alone is a pretty strong argument to return a `Maybe SrcLoc`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9946#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC