#3851: type family does not get expanded in ghc-6.12.1
---------------------------------+------------------------------------------
    Reporter:  kosmikus          |       Owner:                           
        Type:  bug               |      Status:  new                      
    Priority:  normal            |   Component:  Compiler (Type checker)  
     Version:  6.12.1            |    Keywords:                           
          Os:  Unknown/Multiple  |    Testcase:                           
Architecture:  Unknown/Multiple  |     Failure:  GHC rejects valid program
---------------------------------+------------------------------------------
 The following code (which is a trimmed down version of an application of
 the multirec library) does not compile on ghc-6.12.1,
 but it does with ghc-6.10.4. Why?

 {{{
 {-# LANGUAGE GADTs, TypeFamilies #-}
 type family TF a :: * -> *
 type instance TF () = App (Equ ())

 data Equ ix ix' where Refl :: Equ ix ix
 data App f x = App (f x)

 -- does not typecheck in 6.12.1 (but works in 6.10.4)
 bar :: TF () () -> ()
 bar (App Refl) = ()

 -- does typecheck in 6.12.1 and 6.10.4
 ar :: App (Equ ()) () -> ()
 ar (App Refl) = ()
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3851>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to