
#10487: DeriveGeneric breaks when the same data name is used in different modules -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1081 -------------------------------------+------------------------------------- Comment (by osa1): Simon asked for a concrete example and some explanations on Phabricator thread so here it is: (I'm just learning this stuff so there may be mistakes) When we ask GHC to derive a Generic instance, it generates some instances other than Generic, and it also generates new data types for constructors of the type(and I think also for fields of constructors). Let's say I have this: {{{ module N where import GHC.Generics data Name = N1 String | N2 Int deriving instance Generic Name }}} GHC generates these instances: {{{ instance GHC.Generics.Generic N.Name where GHC.Generics.from (N.N1 g1_a17z) = ... GHC.Generics.from (N.N2 g1_a17A) = ... GHC.Generics.to (...) = ... GHC.Generics.to (...) = ... instance GHC.Generics.Datatype N.D1Name where GHC.Generics.datatypeName _ = "Name" GHC.Generics.moduleName _ = "N" instance GHC.Generics.Constructor N.C1_0Name where GHC.Generics.conName _ = "N1" instance GHC.Generics.Constructor N.C1_1Name where GHC.Generics.conName _ = "N2" }}} and these new data types: {{{ N.D1Name N.C1_0Name N.C1_1Name N.S1_0_0Name N.S1_1_0Name }}} Now the problem is, if I have something like this: {{{ module N where import GHC.Generics import qualified M as Blah data Name = Name deriving instance Generic Blah.Name deriving instance Generic Name --- module M where data Name = Name }}} It generates same data types and instances(including head parts, because generated data types are same so instance heads have to refer to same names) for both Names. This leads to duplicate data type and instance declarations. What I did for D1081 so far was to add module names as prefix to generated data types. It worked fine(currently validates), but if we use package imports it should break. So we thought maybe we should use qualified names of modules as a prefix. In our case, that would mean generating `Blah_` prefixed types for `Name` in module `M`, and non-prefixed types for `Name` in current module. With package imports the user need to give modules different names so this should work. But it turns out to be hard to implement, because at the point we're generating instance code, we don't have any knowledge about qualified imports. `RdrName`s are eliminated during renaming. With some experiments I realized `Outputable.PrintUnqualified` doesn't give this info etc. That's where I got stuck. We thought of some solutions: - Add `RdrName` as a field to `Name`. `Name` is a pretty central data type and we may not want to change it. Also, this probably means changing a lot of other code. - Pass `RdrName`s through type checker. No changes in any data types, but we still need to change a lot of other code, functions etc. just to pass this argument through. - (We had the idea of using `Outputable.PrintUnqualified` data but that won't work) I must mention, I don't have an example with package imports. Maybe GHC is already giving modules different names when package imports is used? That would solve everything. I'll try to build a broken(with my patch) example today. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10487#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler