#7352: this type signature in a case alternative does not typecheck and requires
ScopedTypeVariables
------------------------------+---------------------------------------------
 Reporter:  atnnn             |          Owner:  atnnn                  
     Type:  bug               |         Status:  new                    
 Priority:  normal            |      Component:  Compiler (Type checker)
  Version:  7.6.1             |       Keywords:                         
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple       
  Failure:  None/Unknown      |       Testcase:                         
Blockedby:                    |       Blocking:                         
  Related:                    |  
------------------------------+---------------------------------------------

Comment(by atnnn):

 Turning on -ddump-tc-trace makes GHC panic on the declaration of E

 {{{
 {-# LANGUAGE PolyKinds, DataKinds, GADTs #-}

 data T a = T

 data E a where
   E :: T a -> E '[a]
 }}}

 {{{
 tc_lhs_type:
   a
   Expected kind: k_af0
 lk1 a
 lk2 a AThing k_aeU
 checkExpectedKind
   a
   k_aeU
   Expected kind: k_af0
 writeMetaTyVar k_aeY := k_af0
 checkExpectedKindghc-stage2: panic! (the 'impossible' happened)
   (GHC version 7.7.20121020 for x86_64-unknown-linux):
         AThing evaluated unexpectedly tcTyVar a{tv aeN}
 }}}

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