#5792: PolyKinds and recompilation causes internal error
--------------------------------+-------------------------------------------
 Reporter:  reinerp             |          Owner:                         
     Type:  bug                 |         Status:  new                    
 Priority:  normal              |      Component:  Compiler (Type checker)
  Version:  7.4.1-rc1           |       Keywords:                         
       Os:  MacOS X             |   Architecture:  Unknown/Multiple       
  Failure:  Compile-time crash  |       Testcase:                         
Blockedby:                      |       Blocking:                         
  Related:                      |  
--------------------------------+-------------------------------------------
 Given these two files:
 {{{
 module A where
 -- empty
 }}}

 and

 {{{

 {-# LANGUAGE PolyKinds, TypeFamilies, UndecidableInstances #-}
 module B where

 import A

 data T = TT

 type family Compare (m :: T) :: Ordering
 type instance Compare TT = Compare TT

 type Compare' a = Compare a
 }}}

 We can cause an internal GHC error as follows:

 {{{
 $ rm *.o *.hi
 $ ghc B.hs
 [1 of 2] Compiling A                ( A.hs, A.o )
 [2 of 2] Compiling B                ( B.hs, B.o )
 $ sleep 1
 $ touch B.hs
 $ ghc B.hs
 [2 of 2] Compiling B                ( B.hs, B.o )

 B.hs:11:19:
     GHC internal error: `Compare' is not in scope during type checking,
 but it passed the renamer
     tcl_env of environment: [(a9R, AThing k_a9U)]
     In the type `Compare a'
     In the type synonym declaration for Compare'
 }}}

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