
This succeeds, but shouldn't: module A(T) where data T = Foo module B where import A(T(..)) f = Foo

Quite right - the export spec for that type should
now be honoured.
thanks,
--sigbjorn
----- Original Message -----
From: "Ross Paterson"
This succeeds, but shouldn't:
module A(T) where data T = Foo
module B where import A(T(..)) f = Foo

On Thu, Sep 12, 2002 at 06:51:29AM -0700, Sigbjorn Finne wrote:
Quite right - the export spec for that type should now be honoured.
There's something wrong with cumulative exports: module A(Type, Type(Constr)) where data Type = Constr module B where import A(Type(..)) f = Constr fails when it shouldn't, but is OK if .. is replaced by Constr.

Another one that should fail but doesn't: module A(method) where class Class a where method :: a -> a module B where import A f :: Class a => a -> a f = method Exporting a method shouldn't add in its class (ditto fields and types I suppose).

Blimey, who writes code like that? Will have to think about
whether there's a low-impact way of accommodating this with
the current internal representation of export lists.
--sigbjorn
----- Original Message -----
From: "Ross Paterson"
Another one that should fail but doesn't:
module A(method) where class Class a where method :: a -> a
module B where import A f :: Class a => a -> a f = method
Exporting a method shouldn't add in its class (ditto fields and types I suppose). _______________________________________________ Cvs-hugs mailing list Cvs-hugs@haskell.org http://www.haskell.org/mailman/listinfo/cvs-hugs

On Thu, Sep 12, 2002 at 04:20:11PM -0700, Sigbjorn Finne wrote:
Blimey, who writes code like that? Will have to think about whether there's a low-impact way of accommodating this with the current internal representation of export lists.
Yeah, it is a bit perverse. I was looking at the way you treated parents in the code and thought this might slip past. I haven't seen this in the wild (unlike the other one, which is in Hugs.Prelude + Data.Ratio).

Ross Paterson
On Thu, Sep 12, 2002 at 04:20:11PM -0700, Sigbjorn Finne wrote:
Blimey, who writes code like that? Will have to think about whether there's a low-impact way of accommodating this with the current internal representation of export lists.
Yeah, it is a bit perverse. I was looking at the way you treated parents in the code and thought this might slip past. I haven't seen this in the wild (unlike the other one, which is in Hugs.Prelude + Data.Ratio).
I believe I've made the necessary changes to support exports of methods/fields, but not their parent entities. Ditto for cumulative exports, allthough I'll do some more testing in this area. thanks a lot for the help in rooting out all these bugs. --sigbjorn
participants (2)
-
Ross Paterson
-
Sigbjorn Finne