[GHC] #14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: | Owner: (none) mizunashi_mana | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When I use PatternSynonyms + RecordWildCards/NamedFieldPuns, I get name shadowing warnings. I am hoping that these warnings don't trigger in the below case. {{{#!hs {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE NamedFieldPuns #-} module TestPatternSynonyms where pattern Tuple :: a -> b -> (a, b) pattern Tuple{x, y} = (x, y) {-# COMPLETE Tuple #-} f :: (a, b) -> a f Tuple{x} = x {- warning: [-Wname-shadowing] This binding for ‘x’ shadows the existing binding -} g :: (Int, Int) -> Int g Tuple{..} = x + y {- warning: [-Wname-shadowing] This binding for ‘x’ shadows the existing binding This binding for ‘y’ shadows the existing binding -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mizunashi_mana): * failure: None/Unknown => Incorrect error/warning at compile-time -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Hrm, I'm not sure how to fix this. The issues lies with the `is_shadowed_gre` function in `RnUtils`, defined [http://git.haskell.org/ghc.git/blob/7a25659efc4d22086a9e75dc90e3701c1706c625... here]: {{{#!hs is_shadowed_gre :: GlobalRdrElt -> RnM Bool -- Returns False for record selectors that are shadowed, when -- punning or wild-cards are on (cf Trac #2723) is_shadowed_gre gre | isRecFldGRE gre = do { dflags <- getDynFlags ; return $ not (xopt LangExt.RecordPuns dflags || xopt LangExt.RecordWildCards dflags) } is_shadowed_gre _other = return True }}} This uses the `isRecFldGRE` function to detect record selectors, which is in turn defined [http://git.haskell.org/ghc.git/blob/649e777211fe08432900093002547d7358f92d82... as follows]: {{{#!hs isRecFldGRE :: GlobalRdrElt -> Bool isRecFldGRE (GRE {gre_par = FldParent{}}) = True isRecFldGRE _ = False }}} The problem is that pattern synonym record selectors don't use `FldParent` as their `Parent`, but rather `NoParent`. At first, I thought this might have been an oversight, but it turns out there's a reason for this, as explained in [http://git.haskell.org/ghc.git/blob/649e777211fe08432900093002547d7358f92d82... this comment]:
Record pattern synonym selectors are treated differently. Their parent information is `NoParent` in the module in which they are defined. This is because a pattern synonym `P` has no parent constructor either.
So it seems that we need to adjust `isRecFldGRE` to be aware of this fact somehow. But I doubt that having `isRecFldGRE` return `True` whenever it sees //any// occurrence of `NoParent` is the right thing to do... any ideas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #11228 Comment: This is likely related in nature to #11228 (Interaction between ORF and record pattern synonyms needs to be resolved.), since `FldParent` is used to disambiguate duplicate record fields in the presence of `DuplicateRecordFields`. This means that this program will not compile: {{{#!hs {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE PatternSynonyms #-} module Bug where pattern Foo :: Int -> Int -> (Int, Int) pattern Foo {x, y} = (x, y) pattern Bar :: Int -> Int -> (Int, Int) pattern Bar {x, y} = (x, y) }}} Whereas if `x` and `y` were normal record selectors from a data type constructor, GHC would accept them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: adamgundry (added) Comment: Adam Gundry may want to comment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: mpickering (added) Comment: I agree with Ryan's analysis. Now that we have pattern synoyms with record fields, I think we need to disentangle two aspects of `Parent` that are now orthogonal: * whether the `Name` has a parent at all (this can change due to pattern- synonym bundling) * whether the `Name` is a record field, and if so, its label (this shouldn't change) For example, we could add a constructor to `Parent` that has a `Maybe FieldLabelString` but not a parent `Name`. This ought to be enough to make `isRecFldGRE` accurate and hence calculate the name shadowing warnings correctly (fixing this ticket). However, this isn't quite enough for #11228, for which there are other complications (see discussion on https://github.com/ghc-proposals/ghc- proposals/pull/84). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #11228 => #11228, #11970 Comment: Oh bother. Just as I finished up a patch for this, I realized that at one point in time, GHC did exactly what was described in comment:5 by having a `Parent` constructor named `PatternSynonym`. However, `PatternSynonym` was deliberately removed in e660f4bf546e90fb6719ad268ca3daaecdce4b82 (#11970)! Looking at that commit, my patch essentially just adds all of that functionality back plus some changes to `isRecFldGRE`. I'm not sure how to proceed from here—I don't want to trample on other people's work! mpickering, you authored of that commit: do you have an opinion on this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Adam Gundry: you may want to comment too. I'm not sure that the overloaded-record-field stuff is causing all this pain, but it's certainly complicating it. I don't have it anything lie paged in so I'd love it if you felt able to take a careful look. (I think you've been considering some simplifications of the overloaded-record-field stuff that may make things simpler, too.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Do you have your patch Ryan? comment:5 seems to suggest to me implementing `isRecFldGRE` directly rather than indirectly by checking about anything to do with the parent. This is however not what Adam suggested but by disentangle I would imagine two distinct data types, one which tracks parenthood and and one which tracks whether a GRE is a record field. However, if this is the only place in the whole compiler where it matters then perhaps the implementation of this bit should be reconsidered before threading through this extra information everywhere. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): mpickering, my patch is located here: https://github.com/RyanGlScott/ghc/commit/e1262b33092e8b3e2d8bfed588334d14aa... . The main highlights are that it adds a new constructor to `AvailInfo` and `Parent` corresponding to pattern synonym record fields. As I discovered, this is remarkably close to what the state of affairs was pre-#11970 (although back then the information tracked whether a name was a pattern synonym, not necessarily a pattern synonym record field, so perhaps I'm comparing apples to oranges). I'd certainly be open to a simpler approach, although it's not entirely clear to me at the moment what that would be. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): If the check happened later and you could use `Id`s then calling `isRecordSelector` would be appropriate. However, this check looks far too aggressive anyway, if you ever shadow a selector in a module with `RecordWildCards` enabled then you don't get a warning. {{{ {-# LANGUAGE RecordWildCards #-} module Foo where data T = T {a :: Int } -- No warning about a qux (T b) = let a = 2 in 5 }}} In general it looks like the code dealing with shadowing could do with some attention. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:10 mpickering]:
In general it looks like the code dealing with shadowing could do with some attention.
I fully agree with you there. That being said, my sole motivation was to get normal record selectors and pattern synonym record selectors on equal footing, not to fix every issue with record selectors under the sun :) For the time being, at least, the most direct path forward would be finding the minimum API change that would be necessary to achieve the former goal. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I would just tell the user to turn off the shadowing warning rather than commit to a +150 line patch which may never be improved. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14630: name shadowing warnings by record pattern synonyms + RecordWildCards or NamedFieldPuns -------------------------------------+------------------------------------- Reporter: mizunashi_mana | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11228, #11970 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): In the past (prior to Phab:D761), the `RecFieldEnv` stored the set of record field names defined in the current module, and `is_shadowed_gre` used this set for local identifiers and `isRecordSelector` for imported identifiers. We could go back to doing something similar. However, in order to implement `DuplicateRecordFields`, it's helpful for a GRE to simply know whether or not it is a record field (and the field label, if it is), because the renamer ends up special-casing the treatment of multiple in-scope GREs when they are all fields. I think we should keep doing this, and moreover make it correct for record pattern synonym fields, as a step towards #11228. That is, I think we should do something like Ryan's patch. The price we end up paying is a slightly more complicated definition of `AvailInfo`, but I don't think that's too terrible, is it?
I would imagine two distinct data types, one which tracks parenthood and and one which tracks whether a GRE is a record field.
Yes, I think this would be worth doing instead of a new constructor in `Parent`. In the presence of record pattern synonyms, these two properties are independent, and they could simply be two separate fields of `GlobalRdrElt`. Unfortunately I doubt we can really make things fundamentally simpler without doing away with `DuplicateRecordFields` altogether; the simplifications I'm considering will move work from the typechecker to the renamer, but the issues here are all about the renamer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14630#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC