#6020: "Couldn't match kind" with free type variables and PolyKinds
----------------------------------------+-----------------------------------
  Reporter:  atnnn                      |          Owner:                  
      Type:  feature request            |         Status:  new             
  Priority:  normal                     |      Milestone:                  
 Component:  Compiler                   |        Version:  7.5             
Resolution:                             |       Keywords:                  
        Os:  Unknown/Multiple           |   Architecture:  Unknown/Multiple
   Failure:  GHC rejects valid program  |     Difficulty:  Unknown         
  Testcase:  polykinds/T6020            |      Blockedby:                  
  Blocking:                             |        Related:                  
----------------------------------------+-----------------------------------
Changes (by atnnn):

  * status:  closed => new
  * resolution:  fixed =>


Comment:

 If I switch to equality constraints and reverse the functional dependency
 of Id, I get the same error as above ({{{Couldn't match kind `k0' with
 `Bool'}}}):

 {{{
 {-# LANGUAGE DataKinds, FunctionalDependencies, FlexibleInstances,
              UndecidableInstances, PolyKinds, KindSignatures,
              ConstraintKinds, FlexibleContexts, GADTs #-}

 class Id (a :: k) (b :: k) | b -> a
 instance a ~ b => Id a b

 class Test (x :: a) (y :: a)
 instance (Id x y, Id y z) => Test x z

 test :: Test True True => ()
 test = ()

 main = print test
 }}}

 If I comment out `main`, it loads fine but GHC now panics when I use
 `test`:

 {{{
 >>> :load "testid.hs"
 >>> test
 ghc-stage2: panic! (the 'impossible' happened)
   (GHC version 7.5.20120425 for x86_64-unknown-linux):
         tcTyVarDetails k0{tv alS} [tv]
 }}}

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