#5892: Compiler crash and other oddities when using RecordWildCards with fields
not imported
--------------------------------+-------------------------------------------
 Reporter:  parcs               |          Owner:                  
     Type:  bug                 |         Status:  new             
 Priority:  normal              |      Component:  Compiler        
  Version:  7.4.1               |       Keywords:                  
       Os:  Unknown/Multiple    |   Architecture:  Unknown/Multiple
  Failure:  Compile-time crash  |       Testcase:                  
Blockedby:                      |       Blocking:                  
  Related:                      |  
--------------------------------+-------------------------------------------
 GHC exhibits an irrefutable pattern failure when attempting to compile or
 interpret a module that uses the RecordWildCards extension to bind a
 record's field names when its field accessors are not in scope.

 Error:

 {{{
 *** Exception: compiler/rename/RnPat.lhs:535:39-79: Irrefutable pattern
 failed for pattern gres@(gre : _)
 }}}

 Examples:

 {{{
 {-# LANGUAGE RecordWildCards #-}
 import Data.Tree (Tree(Node))
 -- Note that Node's record accessors 'subForest' and 'rootLabel' are not
 imported.

 Node{..} = Node () []
 }}}

 {{{
 {-# LANGUAGE RecordWildCards #-}
 import Data.Tree (Tree(Node))

 foo = let rootLabel = (); subForest = [] in Node{..}
 }}}

 With GHC HEAD + a trivial patch for RnPat.lhs the programs compiled but
 other oddities appeared. With the patch, the first program does not have
 the names 'subForest' and 'rootLabel' in scope, and the second program
 causes GHCi to complain that the names 'rootLabel' and 'subForest' are
 unused, and that the fields 'Data.Tree.rootLabel' and
 'Data.Tree.subForest' are not initialized in the constructor 'Node'.

 I'm not sure what the correct behavior should be in these edge cases but
 thankfully I found a workaround in my program. (I was using
 RecordWildCards to extract the fields of Text.Parsec.Token.TokenParser on
 to the top level. If I don't import its record accessors I get the
 described error, and if I import the accessors unqualified I get ambiguous
 name errors, so instead I just import them qualified.)

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5892>
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