[GHC] #13755: GHC-8.0.2+ spits out $dm names in error messages

#13755: GHC-8.0.2+ spits out $dm names in error messages -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Example (copied from #12881) {{{ {-# LANGUAGE FlexibleInstances #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance Arbitrary a instance Arbitrary Int }}} Error message is: {{{ GHCInstance.hs:10:10: error: • Overlapping instances for Foo Int arising from a use of ‘Main.$dmfoo’ Matching instances: instance Foo a -- Defined at GHCInstance.hs:9:10 instance Foo Int -- Defined at GHCInstance.hs:10:10 • In the expression: Main.$dmfoo @Int In an equation for ‘foo’: foo = Main.$dmfoo @Int In the instance declaration for ‘Foo Int’ }}} Another example: code in #13754 description. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13755 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13755: GHC-8.0.2+ spits out $dm names in error messages -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonpj: @@ -17,2 +17,3 @@ - • Overlapping instances for Foo Int - arising from a use of ‘Main.$dmfoo’ + T13755.hs:9:10: error: + • Overlapping instances for Arbitrary Int + arising from a use of ‘Bug.$dmshrink’ @@ -20,5 +21,5 @@ - instance Foo a -- Defined at GHCInstance.hs:9:10 - instance Foo Int -- Defined at GHCInstance.hs:10:10 - • In the expression: Main.$dmfoo @Int - In an equation for ‘foo’: foo = Main.$dmfoo @Int - In the instance declaration for ‘Foo Int’ + instance Arbitrary a -- Defined at T13755.hs:8:10 + instance Arbitrary Int -- Defined at T13755.hs:9:10 + • In the expression: Bug.$dmshrink @Int + In an equation for ‘shrink’: shrink = Bug.$dmshrink @Int + In the instance declaration for ‘Arbitrary Int’ New description: Example (copied from #12881) {{{ {-# LANGUAGE FlexibleInstances #-} module Bug where class Arbitrary a where shrink :: a -> [a] shrink _ = [] instance Arbitrary a instance Arbitrary Int }}} Error message is: {{{ GHCInstance.hs:10:10: error: T13755.hs:9:10: error: • Overlapping instances for Arbitrary Int arising from a use of ‘Bug.$dmshrink’ Matching instances: instance Arbitrary a -- Defined at T13755.hs:8:10 instance Arbitrary Int -- Defined at T13755.hs:9:10 • In the expression: Bug.$dmshrink @Int In an equation for ‘shrink’: shrink = Bug.$dmshrink @Int In the instance declaration for ‘Arbitrary Int’ }}} Another example: code in #13754 description. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13755#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13755: GHC-8.0.2+ spits out $dm names in error messages -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I agree it's not great. But it's hard even to say what we'd ''like'' it to say, given that the error arises from filling in the default methods. What would you like it to say? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13755#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13755: GHC-8.0.2+ spits out $dm names in error messages -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #10087 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #10087 Comment: #10087 is very closely related to this ticket. The context of #10087 is a bit different since it was talking about `DefaultSignatures`, e.g., {{{#!hs {-# LANGUAGE DefaultSignatures #-} class C a where reflexive :: a -> Bool default reflexive :: Eq a => a -> Bool reflexive x = x == x data D instance C D where }}} {{{ /home/abel/play/haskell/bugs/DefaultSig.hs:10:10: No instance for (Eq D) arising from a use of ‘Main.$gdmreflexive’ In the expression: Main.$gdmreflexive In an equation for ‘reflexive’: reflexive = Main.$gdmreflexive In the instance declaration for ‘C D’ }}} The consensus on that ticket is that we should instead print an error message to the effect of: {{{ No instance for (Eq D) arising from the generic default method for `reflexive` In the instance declaration for ‘C D’ }}} Following the same principle, I think an ideal error message for your particular example would be: {{{ • Overlapping instances for Arbitrary Int arising from a default implementation of `shrink` ... • In the instance declaration for ‘Arbitrary Int’ }}} Do you agree, zilinc? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13755#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13755: GHC-8.0.2+ spits out $dm names in error messages -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #10087 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by zilinc): Thanks Ryan --- I didn't know the internal name leakage had been an issue for quite a while. As a '''user''', if I didn't know what `$dm` or `$gdm` means, it could be hard to see `$dgmreflective` actually refers to `reflective`, esp. there's no delimiter between the prefix and the real name. The bottom line for me, personally, is to avoid the `$` prefixes (stepping back even further, if we couldn't, at least explain it in the user guide). If we could do better, Ryan's suggestion makes perfect sense. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13755#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13755: GHC-8.0.2+ spits out $dm names in error messages -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #10087 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Fixing this infelicity isn't fundamentally hard, but it's a bit fiddly. I can advise if anyone (Ryan?) wants to take it up. The challenge is this: * In an instance declaration, the default method {{{ reflextive = $dgmreflective @ty }}} is generated as `HsSyn Name`; and then fed to the type checker. There are excellent reasons for doing this, rather than (say) generating something in already-typechecked form. * (Something similar happens for ordinary default methods, but it'd be `$dmreflective`. * When typechecking this binding the typechecker doesn't a-prori know that it's special, with a funny name in it. * So the typechecker needs to "know" somehow that this `Id` is special. One way to do that would be to add a form of `IdDetails` to say "I'm a default method Id". Then the "arising from ..." stuff could print a better message. * That would not be hard; these Ids are built in one place, by `mkDefaultMethodIds`. I have not worked out all the details, but am happy to advise. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13755#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13755: GHC-8.0.2+ spits out $dm names in error messages -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #10087, #12854 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #10087 => #10087, #12854 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13755#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC