#3297: Compiler panic on incorrect code (TcTyFuns.flattenType: synonym family 
in a
rank-n type)
----------------------+-----------------------------------------------------
Reporter:  hesselink  |          Owner:                         
    Type:  bug        |         Status:  new                    
Priority:  normal     |      Component:  Compiler (Type checker)
 Version:  6.11       |       Severity:  normal                 
Keywords:             |       Testcase:                         
      Os:  Linux      |   Architecture:  x86                    
----------------------+-----------------------------------------------------
 On the following code sample the compiler panics with:

 {{{
  ghc: panic! (the 'impossible' happened)
   (GHC version 6.11.20090403 for i386-unknown-linux):
         TcTyFuns.flattenType: synonym family in a rank-n type
 }}}

 I found this when working on some code when I made a mistake; the code
 should not type check, but should probably not crash the compiler either.
 I simplified the code to:

 {{{
 {-# LANGUAGE TypeFamilies
            , KindSignatures
            , RankNTypes
            #-}

 type family PF a :: (* -> *) -> * -> *

 class Ix a where
     type Es a :: * -> *
     from  :: a          -> PF a (Es a) a

 crash :: (forall n. Es a n) -> a
 crash = from
 }}}

 It seems similar to #3101, but that one was about data types. A similar
 example also seems to be in #1897, but this bug doesn't seem to fit that
 ticket's description.

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

Reply via email to