[GHC] #7838: ghc(i) crashes on instance declaration

GHC cvs-ghc at haskell.org
Mon Apr 15 08:48:55 CEST 2013


#7838: ghc(i) crashes on instance declaration
-----------------------------+----------------------------------------------
Reporter:  alios             |          Owner:                       
    Type:  bug               |         Status:  new                  
Priority:  normal            |      Component:  Compiler             
 Version:  7.6.2             |       Keywords:  MultiParamTypeClasses
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple     
 Failure:  None/Unknown      |      Blockedby:                       
Blocking:                    |        Related:                       
-----------------------------+----------------------------------------------
 {{{
 multiple lines, ''no wiki''

 {-# LANGUAGE MultiParamTypeClasses, TypeFamilies, ConstraintKinds,
 UndecidableInstances, FunctionalDependencies, FlexibleInstances #-}


 {-
 after declaring the instance

 instance TS TST TT m where

 below my ghci crashes on arch linux x86_64, if you comment it out no crash
 happens.

 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.2 for x86_64-unknown-linux):
         getClassPredTys
 <<details unavailable>>

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



 module Crash where

 class T t where
   type TPI t :: *

 class (T t, C (TPI t) m (TPI t)) => TC c t m | c -> t

 class (T t, C (TPI t) m (TPI t)) => TS s t m | s -> t

 data C i m o

 data TST

 data TT

 instance TS TST TT m where

 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7838>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list