#7527: Couldn't match kind `*' with `*' with PolyKinds & GADTs.
--------------------------------------+-------------------------------------
Reporter:  Ashley Yakeley             |          Owner:                         
    Type:  bug                        |         Status:  new                    
Priority:  normal                     |      Component:  Compiler (Type checker)
 Version:  7.6.1                      |       Keywords:                         
      Os:  Unknown/Multiple           |   Architecture:  Unknown/Multiple       
 Failure:  GHC rejects valid program  |      Blockedby:                         
Blocking:                             |        Related:                         
--------------------------------------+-------------------------------------
 {{{
 {-# LANGUAGE ExistentialQuantification, DataKinds, PolyKinds,
 KindSignatures, GADTs #-}
 module TestKindMatching where
     import GHC.Exts hiding (Any)

     data WrappedType = forall a. WrapType a

     data T (wt :: WrappedType)

     class P (p :: WrappedType -> *) where
          get :: T wt -> p wt

     data W :: (k -> *) -> WrappedType -> * where
         MkW :: forall (f :: k -> *) (a :: k). (f a) -> W f (WrapType a)

     instance P (W (f :: * -> *)) where
         get = get

     thing :: forall (a :: *) (f :: * -> *). T (WrapType a) -> f a
     thing t = case (get t) of
         MkW cw -> cw
 }}}

 {{{
 $ ghc -c TestKindMatching.hs

 TestKindMatching.hs:20:9:
     Couldn't match kind `*' with `*'
     Expected type: a1
       Actual type: a
     Kind incompatibility when matching types:
       a :: *
       a1 :: *
     In the pattern: MkW cw
     In a case alternative: MkW cw -> cw
 }}}

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