#2723: Unnecessary warning for record wildcards
---------------------------------+------------------------------------------
    Reporter:  judah             |       Owner:                  
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Component:  Compiler        
     Version:  6.8.3             |    Severity:  normal          
    Keywords:                    |    Testcase:                  
Architecture:  Unknown/Multiple  |          Os:  Unknown/Multiple
---------------------------------+------------------------------------------
 When compiling a file with record wildcards, -Wall produces a warning
 about shadowed bindings.  Since the presence of a wildcard indicates that
 the shadowing was intentional, this warning seems unnecessary.

 I reproduced this with both 6.8.3 and 6.10.0.20081007:

 {{{
 {-# LANGUAGE RecordWildCards #-}
 module WildCard where

 data Record = Record {field1 :: Int, field2 :: Double}

 test :: Record
 test = let
     field1 = 10
     field2 = 10.0
     in Record {..}
 }}}

 {{{
 $ ghc --make -Wall WildCard.hs
 [1 of 1] Compiling WildCard         ( WildCard.hs, WildCard.o )

 WildCard.hs:8:4:
     Warning: This binding for `field1' shadows the existing binding
                defined at WildCard.hs:4:22
              In the binding group for: field1, field2

 WildCard.hs:9:4:
     Warning: This binding for `field2' shadows the existing binding
                defined at WildCard.hs:4:37
              In the binding group for: field1, field2
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2723>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to