#5633: TypeFamilies don't seem to play with LIberalTypeSynonyms
-------------------------+--------------------------------------------------
Reporter: ocharles | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.4 | Keywords: TypeFamilies LiberalTypeSynonyms
Testcase: | Blockedby:
Os: Linux | Blocking:
Architecture: x86 | Failure: GHC rejects valid program
-------------------------+--------------------------------------------------
I'm trying to do some type level programming and want to use type
families, but also LiberalTypeSynonyms to allow passing in a type level
identity:
The following works:
{{{
{-# LANGUAGE LiberalTypeSynonyms #-}
type Id x = x
type Generic t (i:: * -> *) = i t
foo :: Generic Int Id
foo = undefined
}}}
However, replacing Generic with a type family does not work:
{{{
{-# LANGUAGE LiberalTypeSynonyms #-}
{-# LANGUAGE TypeFamilies #-}
type Id x = x
type family Generic t (i:: * -> *)
type instance Generic Int i = i Int
foo :: Generic Int Id
foo = undefined
}}}
Hopefully I'm not over looking anything, but I can't see why this doesn't
work.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5633>
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