Type families difference between 7.0.4 and 7.2.1

Dan Doel dan.doel at gmail.com
Tue Aug 16 16:56:12 CEST 2011


Classes are not always exported from a module. Only instances are. It
is even possible to export methods of a class that isn't itself
exported, making it impossible to write the types for them explicitly
(GHC will infer qualified types that you can't legally write given the
imports).

I don't really understand why it would be impossible not to export a
data family, given that (instances I understand). And of course, you
can selectively export methods of a class, so why not associated
types?

-- Dan

On Tue, Aug 16, 2011 at 2:16 AM, Brandon Allbery <allbery.b at gmail.com> wrote:
> (I'm adding glasgow-haskell-users to this; if I'm remembering incorrectly
> someone should correct me, if not then the namespace bit should be at least
> mentioned if not filed as a bug.)
> On Tue, Aug 16, 2011 at 00:44, Luite Stegeman <stegeman at gmail.com> wrote:
>>
>> On Tue, Aug 16, 2011 at 6:33 AM, Brandon Allbery <allbery.b at gmail.com>
>> wrote:
>> > On Mon, Aug 15, 2011 at 08:12, Luite Stegeman <stegeman at gmail.com>
>> > wrote:
>> >> -- C.hs
>> >> {-# LANGUAGE TypeFamilies #-}
>> >> module C where
>> >>
>> >> class C1 a where
>> >>  data F a :: *
>> >
>> > I believe this is supposed to be syntactic sugar for a data family, so
>> > 7.0.4
>> > is wrong.  (I also think it was a known deficiency.)
>>
>> In that case, why does module B export F, even though I imported C
>> qualified. Within B it can only be referred to as C.F
>
> My specific recollection is that 7.0.x treated F as a data family without
> calling it one, which introduced some needless duplication in the code base
> and some oddities in usage, including possible core dumps for orphan
> instances.  Again, 7.2.x is the correct reference; behavior of "class ...
> where data ..." in 7.0 is not consistent.
> And yes, not exporting the data-family-not-called-such was one of the
> inconsistencies in 7.0, 7.2's behavior being considered a bug fix for it.
>  7.0's behavior is actually a fairly serious bug, IIRC:  instances of C1 not
> defined within C.hs would not correctly associate with the non-exported data
> family F and the code generated for them would crash at runtime.
>  (Typeclasses are always global over an entire program; in effect, they are
> always exported, and you can't suppress it.  Therefore a data family
> associated with a typeclass must also be exported always.)
> I suspect "Within B it can only be referred to as C.F" is a namespace bug,
> given that F must always be implicitly exported/imported to match the
> implicit export/import of C1.
> --
> brandon s allbery                                      allbery.b at gmail.com
> wandering unix systems administrator (available)     (412) 475-9364 vm/sms
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>



More information about the Glasgow-haskell-users mailing list