Name conflict with DerivingDataTypeable, StandaloneDeriving and qualified imports
The bug is triggered by the following minimal example. Types A.A and B.B share a constructor with the same name. Module B is imported qualified, so that the constructors do not conflict.
A.hs:
module A where
data A = C1 | C2 | C
B.hs:
module B where
data B = D1 | D2 | C
C.hs:
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
module C where
import Data.Data
import Data.Typeable
import A
import qualified B as B
deriving instance Typeable A
deriving instance Typeable B.B
deriving instance Data A
deriving instance Data B.B
main :: IO ()
main = return ()
When deriving a Data instance for the types, I get a name conflict for some generated code:
[au@lift ghc-bug]$ ~/Software/ghc-head/bin/ghc --make C.hs
[1 of 3] Compiling B ( B.hs, B.o )
[2 of 3] Compiling A ( A.hs, A.o )
[3 of 3] Compiling C ( C.hs, C.o )
C.hs:12:1:
Duplicate type signatures for ‛$cC’
at C.hs:11:1-24
C.hs:12:1-26
Note that:
- The problem occurs when deriving Data. Deriving Just the Typeable instance does not produce an error.
- Moving the derivation of Typeable and Data to modules A and B respectively works fine.
The problem occurs both in ghc 7.6.2 as well as in ghc head (rev. cfb9bee7).
Trac metadata
Trac field | Value |
---|---|
Version | 7.7 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |