#1999: panic with GADT etc.
-------------------------+--------------------------------------------------
    Reporter:  jeltsch   |       Owner:       
        Type:  bug       |      Status:  new  
    Priority:  normal    |   Milestone:       
   Component:  Compiler  |     Version:  6.9  
    Severity:  normal    |    Keywords:       
  Difficulty:  Unknown   |    Testcase:       
Architecture:  x86       |          Os:  Linux
-------------------------+--------------------------------------------------
 The following code causes a panic with GHC installed from
 ghc-6.9.20071218-i386-unknown-linux.tar.bz2:
 {{{
 {-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs #-}
 module Bug where

     class C a where

         f :: G a -> ()

     instance (C ()) => C (b c) where

         f (G x) = f x where

     data G a where

         G  :: G () -> G (b c)
 }}}
 The output of ghci is:
 {{{
 GHCi, version 6.9.20071218: http://www.haskell.org/ghc/  :? for help
 Loading package base ... linking ... done.
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )
 ghc-6.9.20071218: panic! (the 'impossible' happened)
   (GHC version 6.9.20071218 for i386-unknown-linux):
         Coercion.splitCoercionKindOf
     base:GHC.Prim.left{(w) tc 34B} $co${tc aog} [tv]
     <pred>b{tv anB} [sk] ~ b{tv aoc} [sk]

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}
 The output of ghc -c is:
 {{{
 ghc-6.9.20071218: panic! (the 'impossible' happened)
   (GHC version 6.9.20071218 for i386-unknown-linux):
         Coercion.splitCoercionKindOf
     base:GHC.Prim.left{(w) tc 34B} $co${tc a6t} [tv]
     <pred>b{tv a5O} [sk] ~ b{tv a6p} [sk]

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

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