[GHC] #10856: Record update doesn't emit new constraints

#10856: Record update doesn't emit new constraints -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I believe this should compile: {{{ {-# LANGUAGE ExistentialQuantification #-} data Rec a b = Show a => Mk { a :: a, b :: b } update :: Show c => c -> Rec a b -> Rec c b update c r = r { a = c } }}} But it fails with {{{ /Users/rae/temp/Bug.hs:6:14: Couldn't match type ‘a’ with ‘c’ ‘a’ is a rigid type variable bound by the type signature for update :: Show c => c -> Rec a b -> Rec c b at /Users/rae/temp/Bug.hs:5:11 ‘c’ is a rigid type variable bound by the type signature for update :: Show c => c -> Rec a b -> Rec c b at /Users/rae/temp/Bug.hs:5:11 Expected type: Rec c b Actual type: Rec a b Relevant bindings include r :: Rec a b (bound at /Users/rae/temp/Bug.hs:6:10) c :: c (bound at /Users/rae/temp/Bug.hs:6:8) update :: c -> Rec a b -> Rec c b (bound at /Users/rae/temp/Bug.hs:6:1) In the expression: r In the expression: r {a = c} }}} I believe the problem has to do with the `fixed_tvs`, the tyvars that are most certainly shared between the initial and result types. The `getFixedTyVars` function always includes tyvars mentioned in constraints. But this is unnecessary. Once the `fixed_tvs` are cleaned up, then we'll also have to make sure to instantiate the constraints necessary to prove that the new constraints are satisfied. We should be careful '''not''' to emit any unchanged constraints, because these are provided by the GADT pattern-match that the desugarer produces. There will probably have to be an update to the `RecordUpd` constructor of `HsExpr` to have a place to put the new dictionaries. NB: This is very related to implementation trouble in Phab:D1152, and I imagine that patch will evolve to fix this infelicity. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10856 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10856: Record update doesn't emit new constraints -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by mpickering): * cc: mpickering (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10856#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10856: Record update doesn't emit new constraints -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): There was a related StackOverflow question about this just yesterday (http://stackoverflow.com/questions/32439605/using-record-update-syntax- with-constrained-gadt-records), coincidence? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10856#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10856: Record update doesn't emit new constraints -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * cc: mpickering (removed) Comment: Is this a more specific description than what's left of #2595? If you (whoever reads this next) agree, then one ticket should be closed as a dup of the other. I'll let you decide which is the dup, because I'm ambivalent. :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10856#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10856: Record update doesn't emit new constraints -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by mpickering): * cc: mpickering (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10856#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC