
What proposals are out there to address the issue of scoping class methods? I always feel I must be careful, when exposing a class definition that I want clients to be able to extend, that I mustn't step on the namespace with semantically appropriate but overly general names (e.g. 'run'). It'd be nice if class method names were module scoped and could be qualified. -- _jsn

I have never run into such an issue. Typically classes tend to have the
smallest possible basis of methods. I would consider a class with more than
about 10 or 15 methods (including superclasses' methods) to indicate poor
design. That is just a rough heuristic.
But you're right, it would be nice if name qualification applied to classes
as well, so that we wouldn't have to worry about it at all.
On Thu, Dec 4, 2008 at 4:53 PM, Jason Dusek
What proposals are out there to address the issue of scoping class methods? I always feel I must be careful, when exposing a class definition that I want clients to be able to extend, that I mustn't step on the namespace with semantically appropriate but overly general names (e.g. 'run'). It'd be nice if class method names were module scoped and could be qualified.
-- _jsn _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

It's not that I like to have a lot of methods in a class, but rather a lot of classes. -- _jsn

No deep inheritance? Then what's the problem?
module X where
class Foo a where foo :: a -> String
module Y where
class Foo' a where foo :: a -> String
module Main where
import qualified X
import qualified Y
instance X.Foo Int where foo _ = "X"
instance Y.Foo' Int where foo _ = "Y"
It is known that the first foo is referring to X.foo, and the second is
referring to Y.foo.
In fact... come to think of it, there are actually no namespace problems.
The instance syntax is just a little quirky, since you don't qualify the
LHS, even if the name is only imported qualified.
Or is that not what you're referring to?
Luke
On Thu, Dec 4, 2008 at 5:43 PM, Jason Dusek
It's not that I like to have a lot of methods in a class, but rather a lot of classes.
-- _jsn
participants (2)
-
Jason Dusek
-
Luke Palmer