Hi,
Looking at some of the ideas in http://www.haskell.org/haskellwiki/The_Other_Prelude , it struck me that the class system at the moment suffers from the problem that as hierarchies get deeper, the programmer is burdened more and more by the need to cut-and-paste method definitions between instances because Haskell doesn't allow a superclass (or ancestor class) method default to be redefined in a subclass.

For example, consider this part of a proposal for Functor => Applicative => Monad:

-- I've just used 'm' so it's easy to see what parts are relevant to Monad
   class Functor m where
           fmap :: (a -> b) -> m a -> m b

   class Functor m => Applicative m where
           return :: a -> m a

           (<*>) :: m (a -> b) -> m a -> m b

           (>>) :: m a -> m b -> m b
           ma >> mb = -- left as exercise for a rainy day!

   class Applicative m => Monad m where
           (>>=) :: m a -> (a -> m b) -> m b

The problem with this is that whereas someone defining a Monad at the moment only needs to define (return) and (>>=), with the above, though it gives obvious advantages in flexibility, generality etc, defining a new Monad involves providing methods (in instance decls) for fmap and (<*>) as well, and the default method for (>>) is

       ma >> mb = (fmap (const id) ma) <*> mb

(from that page above) which I'm sure everyone will agree is a *lot* more complicated than:

       ma >> mb = ma >>= (\_ -> mb)

Not only is the first definition for (>>) more complicated, it obscures the simple fact that for monads it's just a trivial special-use case of >>= where the bound argument is ignored.

Therefore I'm wondering if it would be possible to allow default methods for a superclass to be defined, or redefined, in a subclass, so we could write:

   class Applicative m => Monad m where
           (>>=) :: m a -> (a -> m b) -> m b

           mf <*> ma = mf >>= \f -> ma >>= \a -> return (f a)

           ma >> mb = ma >>= \_ = -> mb

           fmap f ma = ma >>= \a -> return (f a)

(I know the above can be written in a more point-free style but I wrote it like that to make it easy to understand what's happening.)

The essential point here (excuse the pun :-) ) is that it is impossible to write the default methods in the class in which the operation is defined, because the implementation depends on methods of the relevant subclass (and will therefore be different for different subclasses though not for each particular instance of a given ancestor class of a particular subclass). As Haskell stands at the moment, we are forced to cut and paste identical methods for each individual instance of each ancestor class of a particular subclass because we can't override an ancestor class method in the *class* decl for a subclass.

The type class system at present is based on the idea that you can define related methods together and in terms of each other, at one level of the hierarchy. However as the above example shows, related methods sometimes need to be spread over the hierarchy but we still want to be able to define default implementations of them in terms of each other.

Perhaps there is some reason this can't be done?

Brian.
--
http://www.metamilk.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to