[Haskell-cafe] Associated data types and contexts

Eric Walkingshaw walkiner at eecs.oregonstate.edu
Fri Oct 8 07:55:42 EDT 2010


The following code compiles happily in GHC:

> {-# LANGUAGE TypeFamilies #-}
>
> class C a where
>   data D a
>   m :: D a -> Bool
>
> test :: C a => D a -> Bool
> test = m

My question is why do I need the context in the function "test"?  It
seems like since "D" is associated with class "C", the compiler can
safely assume that any time I have a "D a", "a" must be an instance of
C.  But GHC complains if the context is removed.

At first I thought that maybe the associated type was just syntactic
sugar for a non-associated data type family.  But this doesn't seem to
be the case since I cannot instantiate D outside of an instance of C.
Google and the type family documentation provided no other leads.

Am I missing something here?  Is the context assumption invalid?  Or
is it just an assumption that GHC doesn't make (yet)?

Thanks in advance for any replies.

-Eric
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20101008/ef60c180/attachment.html


More information about the Haskell-Cafe mailing list