[GHC] #8607: Invalid location reported for type constructors

#8607: Invalid location reported for type constructors ------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Given {{{ module Example where data T = MkT }}} The locations as reported in 7.4 and 7.7 are different: * In 7.4 the ADT is represented as a `TyData`, itself part of an `HsGroup`. The `TyData` contains a `Located Name`; the location of this name is reported correctly as 3:6. The `SrcSpan` associated with the `Name` itself (which represents the def site) is also reported as 3:6, which is dubious. * In 7.8 the ADT is represented as a `DataDecl` (part of ` TyClGroup` inside a `HsGroup`). As before, the `DataDecl`contains a `Located Name`; the location now however is 3:1-12, which doesn't make sense. The def site associated with the name itself is also 3:1-12, which ''does'' make sense. It seems that when the def site was fixed, it also changed the location of the identifier itself. These two are separate. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): Actually, the def-site as reported by 7.4 is correct (it's the position where the id is defined, not the span of the definition proper). So I think 7.4 is correct about both locations, and 7.7 wrong about both. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): The same problem goes for class definitions; the location of `C` in {{{ class C a where f :: a -> a }}} is reported as the span of the entire class, rather than the span of just the identifier. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): .. and the same for type synonyms .. Location of `Foo` in {{{ type Foo = Int }}} is reported as the entire synonym declaration (1-14 instead of 6-8). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): .. and type families .. Location of `Bar` in {{{ type family Bar a }}} is reported as the entire line (type family instances do appear to be correct). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): Hmmm, this appears to be (partly?) intentional -- https://ghc.haskell.org/trac/ghc/changeset/174577912de7a21b8fe01881a28f5aafc.... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by goldfire): * owner: => goldfire Comment: Yes, it does appear to be somewhat intentional. But, it looks like some plumbing change in !TcTyClsDecls could restore the old behavior. (I'm thinking of returning `TcM [Located TyThing]` from `tcTyClDecl`.) I can take a look at this next week. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): FYI, I sent the following email to SPJ, but he won't be back until next year: In the commit message you say "The only wrinkle is that, since we don't have the original declaration, we don't have its `SrcSpan` to put in the error message". But the function you are talking about is checkValidDecl, right? And that takes a Located Name as argument -- would it be possible to use the nameSrcSpan of the Name instead of the error message? I.e., have the def site of the Name be the entire declaration of the type, but the location of the identifier itself still the actual location of the identifier? Changing the `SrcSpan` associated with the identifier itself is troublesome for IDEs that want to know information about identifiers at particular locations. I'm not 100% how to go about this though, because the parser obviously generates a `RdrName`, not a Name, so we don't yet have the distinction between the location of a name (Located Name) and its nameSrcSpan. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): I'm not sure what chunk of code you're talking about. While I agree that a `Located Name` is redundant, I don't see how that helps us here. It seems to me that the function of interest is `checkValidTyCl`, which just takes a `TyThing`, devoid of any location information other than what is stored in the `n_loc` field of `Name`s. By passing in an extra location (by using `Located TyThing`), we can get good error messages and proper spans on identifiers. I do feel a little dirty decorating the Core-ish `TyThing` with the Haskell-ish `Located`, but I think this is a reasonable place to do so. Other suggestions are welcome. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): Well I'm not familiar at all with this code, so I may be talking nonsense; I just wanted to point out that a `Located Name` is _not_ redundant: a `Located Name` contains two locations, and that's exactly right: one if the location of the identifier, and the other is the def span of whatever the identifier is referring to. The change in this commit changed _both_ of those locations to be the span of the entire type declaration; it seems to be that it ought to be sufficient to change only the `nameSrcSpan` but not the location of the identifier itself. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by goldfire): * owner: goldfire => Comment: So, I took a look at this, and it's ugly. The problem is that each `TyClDecl` can give rise to potentially many top-level things. Of these things, only the `TyCon`s are checked for validity, so we really only need location info for `TyCon`s. It's a little painful returning a `[Located TyThing]` when the `Located` bit applies to only one disjunct of `TyThing`. But, I was willing to deal with that. The real problem comes from the fact that one declaration can actually produce many `TyCon`s: a class with associated types. According to the validity checking code -- which checks all `TyCon`s, top-level and not -- we would need these associated type `TyCon`s to have correct locations. Unfortunately, there is no clean way to get good locations for associated types without polluting the code in `tcClassATs` and possibly `ClassATItem`, which is persisted within the `Class` datatype. Very yuck. Is all of this doable? Absolutely, but it would make Simon wish he had just stayed on holiday. So, I propose that, to fix this problem, we store location information ''in the `TyCon`''. This should be easy to get correct and easy to use. It would be cleaner than adding `Located` in various places throughout !TcTyClsDecls. But, it stores location information in a very Core-ish place, and I would rather consult with others before going ahead with this plan. There is precedent: `CoAxBranch`es store locations for similar reasons. But, of course, I was the chief person behind `CoAxBranch`es, and it's a little silly to use my own design decision as precedent. Thoughts? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by edsko): So correct me if I'm wrong, but -- `TyCon` contains a `Name`, right? And that `Name` has a `nameSrcSpan`. And that `nameSrcSpan` is what is used for error messages (probably through `setSrcSpan (getSrcSpan thing)` at the start of `checkValidTyCl`?). So `TyCon`s ''already'' have a built-in location, and I guess this was precisely the purpose of Simon's patch. I don't have a problem with the `nameSrcSpan` of a `Name` being set to be the location of the entire type declaration. What ''is'' a problem, however, is that in the AST, that name becomes a `Located Name`, for example as in {{{ data TyClDecl name | -- | @data@ declaration DataDecl { tcdLName :: Located name -- ^ Type constructor ... }}} So `Located Name` has ''two'' `SrcSpan`s; one for the `Located` part, and one for the `Name` part (`nameSrcSpan`). The problem is that Simon's patch changed ''both'' of these `SrcSpan`s to point to the entire span of the type declaration. They are logically different -- one tells you where ''this occurrence'' of the identifier is, the other tells you where the identifier is defined. For IDE purposes we need to know accurate information about the location of this occurrence, even if it's `nameSrcSpan` (def site) points somewhere else. Do I make any sense at all? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): Yes, I see what you're saying much better now. But, it still doesn't seem to quite correspond with what's going on in Simon's original change. That commit (1745779...) seems to change only the location in the `Located` bit, not the one in the `nameSrcSpan`. Oh, it's all suddenly clear. Simon's commit was overzealous. It turns out that the location stored in the `Located` bit in a `tcdLName` seems to be ignored in the validity checker -- it's only the location in the `nameSrcSpan` that does any work. So, the changes Simon made to !RdrHsSyn were totally unnecessary to correspond to the refactoring in !TcTyClsDecls. The solution is dead easy: I can just revert the changes in !RdrHsSyn and revert the corresponding changes in the testsuite, while keeping the refactoring in !TcTyClsDecls, which was the whole point to begin with. Have to run now, but will do this later today. Thanks for pointing me in this direction! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors
-------------------------------------+------------------------------------
Reporter: edsko | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Richard Eisenberg

#8607: Invalid location reported for type constructors
-------------------------------------+------------------------------------
Reporter: edsko | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Richard Eisenberg

#8607: Invalid location reported for type constructors
-------------------------------------+------------------------------------
Reporter: edsko | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Richard Eisenberg

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by goldfire): * status: new => closed * resolution: => fixed Comment: See the commit message above for details -- somewhat different than my last Trac post on the subject. The solution I found was much cleaner than what I proposed here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors
-------------------------------------+------------------------------------
Reporter: edsko | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.7
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by edsko):
Replying to [comment:14 Richard Eisenberg
The solution (after many false starts) is to change the behavior of hsLTyClDeclBinders. The idea is that the locations of the names that the parser generates should really be the names' locations, unlike what was done in 1745779... But, when the renamer is creating Names from the RdrNames, the locations stored in the Names should be the declarations' locations. This is now achieved in hsLTyClDeclBinders, which returns [Located name], but the location is that of the *declaration*, not the name itself.
Yes, this sounds like the Right Thing To Do. I have tested our code with this patch applied and it seems to work perfectly. Thank you very much! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8607: Invalid location reported for type constructors -------------------------------------+------------------------------------ Reporter: edsko | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): I like it, thank you. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8607#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC