[Haskell-cafe] Associated data types and contexts

Ryan Ingram ryani.spam at gmail.com
Fri Oct 8 14:27:00 EDT 2010


"D x", for an x that is not an instance of C, is still inhabited by "undefined".

Additionally, on the implementation side, the dictionary C is not
included inside of a D, so you still need to pass it in to call m; a
function
> test :: C a => D a -> Bool
gets translated in Core into a system F type like this:
> data Dict_C a = Dict_C { m :: D a -> Bool }
> test :: forall a. Dict_C a -> D a -> Bool

  -- ryan


On Fri, Oct 8, 2010 at 4:55 AM, Eric Walkingshaw
<walkiner at eecs.oregonstate.edu> wrote:
> 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
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list