#7503: Bug with PolyKinds, type synonyms & GADTs
--------------------------------------+-------------------------------------
Reporter:  Ashley Yakeley             |          Owner:                         
    Type:  bug                        |         Status:  new                    
Priority:  normal                     |      Component:  Compiler (Type checker)
 Version:  7.6.1                      |       Keywords:                         
      Os:  Linux                      |   Architecture:  x86_64 (amd64)         
 Failure:  GHC rejects valid program  |      Blockedby:                         
Blocking:                             |        Related:                         
--------------------------------------+-------------------------------------
 GHC incorrectly rejects this program:
 {{{
 {-# LANGUAGE ExistentialQuantification, DataKinds, PolyKinds,
 KindSignatures, GADTs #-}
 module TestConstraintKinds where
     import GHC.Exts hiding (Any)

     data WrappedType = forall a. WrapType a

     data A :: WrappedType -> * where
         MkA :: forall (a :: *). AW a -> A (WrapType a)

     type AW  (a :: k) = A (WrapType a)
     type AW' (a :: k) = A (WrapType a)

     class C (a :: k) where
         aw :: AW a -- workaround: AW'

     instance C [] where
         aw = aw
 }}}

 GHC accepts the program when AW is replaced with AW' on that line.

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