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.
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Reply via email to