#5372: DisambiguateRecordFields with qualified import can cause panic
---------------------------------+------------------------------------------
    Reporter:  shelarcy          |       Owner:                    
        Type:  bug               |      Status:  new               
    Priority:  normal            |   Component:  Compiler          
     Version:  7.3               |    Keywords:                    
    Testcase:                    |   Blockedby:                    
          Os:  Unknown/Multiple  |    Blocking:                    
Architecture:  Unknown/Multiple  |     Failure:  Compile-time crash
---------------------------------+------------------------------------------
 When I'm using DisambiguateRecordFields with GHC 7.2.1 RC1
 (7.2.0.20110728), I encounter panic.

 {{{
 module M where
 data S = MkS { x :: Int, y :: Bool }
 }}}

 {{{
 {-# LANGUAGE DisambiguateRecordFields #-}
 module Foo where
 import qualified M
 notScope (MkS { x = n }) = n
 }}}

 This code causes panic when using GHC 7.2.1 RC1, and GHC 7.3.20110802.

 {{{
  (snip)
 [1 of 2] Compiling M                ( M.hs, interpreted )
 [2 of 2] Compiling Foo              ( Test.hs, interpreted )
 ghc.exe: panic! (the 'impossible' happened)
   (GHC version 7.3.20110802 for i386-unknown-mingw32):
         find_tycon
     MkS{d 02A}
     []

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

 >
 }}}

 This problem is caused by using DisambiguateRecordFields extention. When I
 remove DisambiguateRecordFields extention from Foo module, GHC doesn't
 cause panic.

 {{{
 module Foo where
 import qualified M
 notScope (MkS { x = n }) = n
 }}}

 {{{
 > :r
 [2 of 2] Compiling Foo              ( Test.hs, interpreted )

 Test.hs:4:11:
     Not in scope: data constructor `MkS'
     Perhaps you meant `M.MkS' (imported from M)

 Test.hs:4:17: `x' is not a (visible) field of constructor `MkS'
 Failed, modules loaded: M.
 *M>
 }}}

 GHC 7.0.4 doesn't cause panic even though using DisambiguateRecordFields
 extention.

 {{{
 [1 of 2] Compiling M                ( M.hs, interpreted )
 [2 of 2] Compiling Foo              ( Test.hs, interpreted )

 Test.hs:4:11: Not in scope: data constructor `MkS'

 Test.hs:4:17: `x' is not a (visible) field of constructor `MkS'
 Failed, modules loaded: M.
 }}}

 So, I think this problem comes from
 5d89565b043eaff9028205b79363ef0d0c17ff17 .

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