#6129: Failure when using promoted data family instances, again
------------------------------+---------------------------------------------
 Reporter:  dreixel           |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  Compiler        
  Version:  7.5               |       Keywords:  PolyKinds       
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown      |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 The following code should fail (since we don't promote data families), but
 it should do so gracefully:
 {{{
 {-# LANGUAGE GADTs        #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE PolyKinds    #-}
 {-# LANGUAGE DataKinds    #-}

 data family D a
 data instance D a = DInt

 data X a where
   X1 :: X DInt
 }}}

 With ghc-7.5.20120513 it produces:
 {{{
     GHC internal error: `DInt' is not in scope during type checking, but
 it passed the renamer
     tcl_env of environment: [(a1t1, AThing k_a1t8),
                              (rVJ, AThing k_a1t8 -> *), (rW1, ANothing)]
     In the type `X DInt'
     In the definition of data constructor `X1'
     In the data declaration for `X'
 }}}

 #5716 seems not to have fixed this particular case.

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