#7474: Panic with zonkQuantifiedTyVar in GHC 7.6.1
-----------------------------+----------------------------------------------
Reporter:  spl               |          Owner:                         
    Type:  bug               |         Status:  new                    
Priority:  normal            |      Component:  Compiler (Type checker)
 Version:  7.6.1             |       Keywords:                         
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple       
 Failure:  None/Unknown      |      Blockedby:                         
Blocking:                    |        Related:                         
-----------------------------+----------------------------------------------
 In GHC 7.6.1, the following code:

 {{{
 {-# LANGUAGE TypeFamilies, GADTs, FlexibleContexts, MultiParamTypeClasses
 #-}

 type family T :: * -> *

 data E :: * -> * where
   E :: C p => T (T p) -> E p

 class C' b a where c :: T b -> a

 class C' (T a) a => C a

 -- f :: C' (T p) a => E p -> a
 f (E d) = c d
 }}}

 produces the following error message:

 {{{
 [1 of 1] Compiling Main             ( Test.hs, interpreted )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for i386-apple-darwin):
         zonkQuantifiedTyVar
 <<details unavailable>>
 }}}

 Uncommented the type signature allows it to compile.

 The code above '''does not''' panic in HEAD, so I guess it's fixed. But I
 thought it would be good to report it anyway.

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