Missing definitions of associated types
David Feuer
david.feuer at gmail.com
Thu Feb 18 17:00:46 UTC 2016
It seems to be that a missing associated type definition should be an
error, by default, rather than a warning. The current behavior under those
circumstances strikes me as very strange, particularly for data families
and particularly in the presence of overlapping.
{-# LANGUAGE TypeFamilies #-}
class Foo a where
data Assoc a
foo :: proxy a -> Assoc a
instance {-# OVERLAPPABLE #-} Foo a where
data Assoc a = AssocGeneral
foo _ = AssocGeneral
instance {-# OVERLAPS #-} Foo Char where
foo _ = AssocGeneral
blah :: Assoc Char
blah = foo (Proxy :: Proxy Char)
This compiles with just a warning because Assoc Char *falls through* to the
general case. WAT? This breaks all my intuition about what associated types
are supposed to be about.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20160218/0baa839e/attachment.html>
More information about the ghc-devs
mailing list