[Haskell] type family vs. polymorphism
Andres Loeh
andres at cs.uu.nl
Mon Jan 12 16:43:58 EST 2009
Hi.
Here's a strange interaction of type families and higher-rank
polymorphism (tested with both ghc-6.8.3 and ghc-6.10.1):
{-# LANGUAGE TypeFamilies, EmptyDataDecls, RankNTypes #-}
data X (a :: *)
type family Y (a :: *)
-- This works (datatype).
i1 :: (forall a. X a) -> X Bool
i1 x = x
-- This works too (type family and extra arg).
i2 :: (forall a. a -> Y a) -> Y Bool
i2 x = x True
-- This doesn't work (type family).
-- i3 :: (forall a. Y a) -> Y Bool
-- i3 x = x
I would expect i3 to be ok as well. Note that this is a
simplified example and not really useful in its simplified
form.
Cheers,
Andres
--
Andres Loeh, Universiteit Utrecht
mailto:andres at cs.uu.nl mailto:mail at andres-loeh.de
http://www.andres-loeh.de
More information about the Haskell
mailing list