[GHC] #15149: Identical distinct type family fields miscompiled

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the code: {{{#!hs -- An.hs {-# LANGUAGE TypeFamilies #-} module An where data family An c :: * -- AnInt.hs {-# LANGUAGE TypeFamilies #-} module AnInt where import An data instance An Int = AnInt {an :: Int} deriving Show -- AnDouble.hs {-# LANGUAGE TypeFamilies #-} module AnDouble where import An data instance An Double = AnDouble {an :: Double} deriving Show -- Main.hs {-# LANGUAGE DisambiguateRecordFields #-} module Main where import AnInt import AnDouble main = print (AnDouble{an=1}, AnInt{an=1}) }}} I would expect this code to work. In reality it fails at runtime with GHC 8.2.2: {{{ Main.hs:4:15-28: warning: [-Wmissing-fields] * Fields of `AnDouble' not initialised: an * In the expression: AnDouble {an = 1} In the first argument of `print', namely `(AnDouble {an = 1}, AnInt {an = 1})' In the expression: print (AnDouble {an = 1}, AnInt {an = 1}) | 6 | main = print (AnDouble{an=1}, AnInt{an=1}) | ^^^^^^^^^^^^^^ *** Exception: Main.hs:4:15-28: Missing field in record construction an }}} And fails at compile time in GHC 8.4.2: {{{ Main.hs:4:31-41: error: * Constructor `AnInt' does not have field `an' * In the expression: AnInt {an = 1} In the first argument of `print', namely `(AnDouble {an = 1}, AnInt {an = 1})' In the expression: print (AnDouble {an = 1}, AnInt {an = 1}) | 6 | main = print (AnDouble{an=1}, AnInt{an=1}) | ^^^^^^^^^^^ }}} This code was extracted from a real example, where this bug is pretty fatal, as I haven't been able to find any workarounds (without just avoiding clashing record fields). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => ORF -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: adamgundry (added) Comment: I investigated. Here is what is going on: * When compiling module `An`, there are two `an`'s in scope * You might resaonably think that with `DisamgiguateRecordFields`, the `an` in `AnInt { an = 1 }` is ''obviously'' the `an` from module `AnInt`. * But in fact GHC's renamer uses the ''type constructor'', not the ''data constructor'' to disambiguate which `an` you mean. And both `an`'s have the same "parent", namely the type constructor `An`. This was fine before data families, because a single type constructor could not have data constructors with distinct `an` record fields. But now it can. A short term fix is to complain about ambiguity rather than arbitrarily picking one (as is done now). This happens here in `TcExpr`: {{{ tcRecordField con_like flds_w_tys (L loc (FieldOcc sel_name lbl)) rhs | Just field_ty <- assocMaybe flds_w_tys sel_name = ... }}} That `assocMaybe` just picks the first. So we could fix that. But how can we fix it properly? After all, all the information is there, staring us in the face. * One way forward might be to say that the data constructor `AnInt` is the "parent" of `AnInt.an`, and the type constructor `An` is the parent of the data constructor `AnInt`. But that change would mean we had a multi-level parent structure, with consequences that are hard to foresee. * But I think a better way is to ''stop'' trying to make the choice in the renamer. Instead in a `HsRecordFields` structure, keep the field names as not-yet-looked-up `OccNames` in the renamer, and look them up in the typechecker. At that point, we have the data constructor available in its full glory and don't need to bother with the tricky parent structures in the renamer. Adam, do you think that would work? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): I think this would work, and would amount to eliminating the distinction between `HsRecField` (containing `FieldOcc`) and `HsRecUpdField` (containing `AmbiguousFieldOcc`). At the moment, the former is used for record construction and pattern matching (fields always resolved by the renamer), while the latter is used for selection and update (ambiguous fields resolved by the type-checker). Here "ambiguous" really means "ambiguous from the renamer's perspective, but not necessarily the type- checker". It would probably be simpler to defer all field resolution to the type- checker, though we've also considered going in the opposite direction, and moving all field resolution back to the renamer (see https://github.com /ghc-proposals/ghc-proposals/pull/84). I'm not really sure which is better! There's an awkward corner if we were to defer all field resolution to the type-checker, which is that `Ambiguous` fields are not currently supported by `DsMeta`. That is, using them inside a TH bracket will fail with a "not supported" error. The basic problem is that `DsMeta` works on renamed syntax, even though it runs after type-checking. Would that be difficult to change? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
It would probably be simpler to defer all field resolution to the type- checker, though we've also considered going in the opposite direction, and moving all field resolution back to the renamer
That proposal (!DuplicateRecordFields simplification) is about simplifying the DRF spec. Yes, it'd make it possible to resolve that particular aspect of record fields in the renamer -- but it by no means requires us to do so.
That is, using them inside a TH bracket will fail with a "not supported" error
My baseline thought is that `C { x = e1, y = e2 }` should have `x` and `y` as `OccNames` right up to the type checker. And that would be so in TH syntax to. In TH we have {{{ data Exp = ... | RecConE [FieldExp] type FieldExp = (Name,Pat) }}} We could consider changing that `Name` to `OccName`, or just using the `NameS` variant of `Name`. No serious problem there. My notion of using `OccName` is a bit ''too'' simple. * It is in principle fine for `C { ... }` in both expressions and patterns, but in fact H98 syntax allows a qualified name there, thus `C { M.x = e }`. That suggests we need a `RdrName` there, not an `OccName`. The type checker can still resolve it, since the name to the LHS of the `=` need consider only the top-level `GlobalRdrEnv` and that is entirely available in the typechecker. * For record update `e { x = e2 }`, the same applies but now the use of qualified names to disambiguate is more important still. I think this boils down to * Remove the `extFieldOcc` field of `data FieldOcc`, leaving only a `Located RdrName`. (In fact we can then inline `FieldOcc`.) * Move the lookup machinery from the renamer to the typechecker Do you think that'd work? Any motivation to try it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): PS, Neil you say
I haven't been able to find any workarounds (without just avoiding clashing record fields).
Can't you just not use `DisambiguateRecordFields` and instead say this? {{{ main = print (AnDouble{AnDouble.an=1}, AnInt{AnInt.an=1}) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): Yes, I can try to take a look at this.
My baseline thought is that `C { x = e1, y = e2 }` should have `x` and `y` as `OccNames` right up to the type checker. And that would be so in TH syntax to.
I agree that this would be simpler (in the presence of `DisambiguateRecordFields`, `DuplicateRecordFields`, etc.). I'm concerned that it might impact TH users though, as they will have only an `OccName` where previously they had a `Name` (and they might not easily be able to reliably look up the `OccName` because of precisely this ticket). Should this go through ghc-proposals, or is there another process for discussing TH changes? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: adamgundry Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14747 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * owner: (none) => adamgundry * related: => #14747 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: adamgundry Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14747 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I'm concerned that it might impact TH users though, as they will have only an OccName where previously they had a Name
Well comment:4 suggests leaving it as `TH.Name`; as subsequent bullets point out, we need correspondingly need `RdrName` not `OccName` in `HsSyn.` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: adamgundry Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14747 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): I think I've come across a simpler way to fix this and #14747. At the moment, `rnHsRecFields` goes to some trouble to figure out the parent type constructor of the data constructor (in `find_tycon`) and then does field name lookup using the parent type constructor. But we already have `lookupConstructorFields` which lets us directly find out the `FieldLabel`s of a data constructor! (This is used for expanding dot-dot patterns.) So why don't we just use `lookupConstructorFields` and search amongst them for the right one? We'd need to be a bit careful to still check the name is in scope (with the right module qualifier, if any), but that should be simple if we know the unambiguous selector name already. Moving field label resolution to the typechecker still might be worth doing, because it should get rid of quite a bit of duplication. But it's not a small task (e.g. because of dot-dot patterns) so I think it's worth pursuing the small fix first. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: adamgundry Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | rename/should_compile/T15149 Blocked By: | Blocking: Related Tickets: #14747 | Differential Rev(s): Phab:D4821 Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * testcase: => rename/should_compile/T15149 * status: new => patch * differential: => Phab:D4821 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Moving field label resolution to the typechecker still might be worth doing, because it should get rid of quite a bit of duplication. But it's not a small task (e.g. because of dot-dot patterns) so I think it's worth
#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: adamgundry Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | rename/should_compile/T15149 Blocked By: | Blocking: Related Tickets: #14747 | Differential Rev(s): Phab:D4821 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): pursuing the small fix first. I agree with this point, but we should still do it! Then we could get rid of `tcg_field_env` altogether, which would be very worthwhile. Maybe open a fresh ticket for it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: adamgundry Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | rename/should_compile/T15149 Blocked By: | Blocking: Related Tickets: #14747, #15277 | Differential Rev(s): Phab:D4821 Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * related: #14747 => #14747, #15277 Comment: I think Phab:D4821 should be good to go with the small fix, and I've opened #15277 for the bigger refactoring. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15149: Identical distinct type family fields miscompiled
-------------------------------------+-------------------------------------
Reporter: NeilMitchell | Owner: adamgundry
Type: bug | Status: patch
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.2
Resolution: | Keywords: ORF
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: GHC rejects | Test Case:
valid program | rename/should_compile/T15149
Blocked By: | Blocking:
Related Tickets: #14747, #15277 | Differential Rev(s): Phab:D4821
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#15149: Identical distinct type family fields miscompiled -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: adamgundry Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.2 Resolution: fixed | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | rename/should_compile/T15149 Blocked By: | Blocking: Related Tickets: #14747, #15277 | Differential Rev(s): Phab:D4821 Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * status: patch => closed * resolution: => fixed * milestone: 8.8.1 => 8.6.1 Comment: This was fixed in 8.6.1, looks like the ticket missed being closed when the patch was merged. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15149#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC