#5592: Incorrect "redundant import" warning
---------------------------------+------------------------------------------
    Reporter:  ryantrinkle       |       Owner:                                 
  
        Type:  bug               |      Status:  new                            
  
    Priority:  normal            |   Component:  Compiler                       
  
     Version:  7.2.1             |    Keywords:                                 
  
    Testcase:                    |   Blockedby:                                 
  
          Os:  Unknown/Multiple  |    Blocking:                                 
  
Architecture:  Unknown/Multiple  |     Failure:  Incorrect warning at 
compile-time
---------------------------------+------------------------------------------
 Record fields are incorrectly deemed "redundant" by GHC in at least some
 circumstances.  This causes a confusing warning when -Wall is on.

 Given the following module,
 {{{
 module MyRecord where

 data MyRecord = MyRecord { field :: String } deriving (Show)
 }}}

 the following program's meaning will change depending on whether or not
 "field" is imported:
 {{{
 {-# LANGUAGE RecordWildCards #-}

 import qualified MyRecord as MR (MyRecord(MyRecord))

 main = do
   let field = "Hello, world!"
       rec = MR.MyRecord {..}
   print rec
 }}}

 The program as written will crash, because the record wildcard will not
 use the 'field' variable, since the 'field' record label is not imported.
 A warning is correctly issued regarding the missing field.

 However, if the user adds an import for 'field',
 {{{
 import qualified MyRecord as MR (MyRecord(MyRecord, field))
 }}}

 GHC will issue a warning:
 {{{
 Main.hs:3:1:
     Warning: The import of `MR.field'
              from module `MyRecord' is redundant
 }}}

 However, adding the import of 'field' causes the record wildcard to have
 access to the 'field' label, so the program does not crash.

 Since the import changes the meaning of the program, it shouldn't be
 considered redundant.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5592>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to