Difference between revisions of "Class system extension proposal"

From HaskellWiki
Jump to navigation Jump to search
m (Changed category to "Proposals")
m (clarified distinction between method and implementation)
Line 3: Line 3:
 
===Motivation===
 
===Motivation===
   
The current class system in Haskell is based on the idea that you can often provide default methods for a class at the same time as defining the class, by using other methods of the class or its ancestors. However consider the following hierarchy, adapted from [[Functor hierarchy proposal]] and [[The Other Prelude]]:
+
The current class system in Haskell is based on the idea that you can often provide default implementations for class methods at the same time as defining the class, by using other methods of the class or its ancestors. However consider the following hierarchy, adapted from [[Functor hierarchy proposal]] and [[The Other Prelude]]:
 
<haskell>
 
<haskell>
 
class Functor m where
 
class Functor m where

Revision as of 00:42, 10 January 2007

Allowing superclass methods to be overridden in derived classes

Motivation

The current class system in Haskell is based on the idea that you can often provide default implementations for class methods at the same time as defining the class, by using other methods of the class or its ancestors. However consider the following hierarchy, adapted from Functor hierarchy proposal and The Other Prelude:

    class Functor m where
        fmap :: (a -> b) -> m a -> m b

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

        apply :: m (a -> b) -> m a -> m b

        (>>) :: m a -> m b -> m b
        ma >> mb = (fmap (const id) ma) `apply` mb

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

For all concrete instances of Monad we can define fmap, apply, and (>>) in terms of return and (>>=) as follows:

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

        apply mf ma = mf >>= \f -> ma >>= \a -> return (f a)

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

In other words, we'd like to be able to write:

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

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

        apply mf ma = mf >>= \f -> ma >>= \a -> return (f a)

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

and be able to define new instances of Monad just by supplying definitions for return and (>>=) by writing:

    instance Monad T where
        ma >>= a_mb = ... -- some definition

        return a = ... -- some definition

However in Haskell at present we can't do this, because we are only allowed to provide default implementations for a class method in the class where the method is introduced (ie the class containing the method signature) and similarly we are only allowed to provide an implementation for a method in an instance for the class itself, not a derived class. Therefore with the above hierarchy, we would have to manually define instances of Functor and Applicative whenever we define an instance of Monad.

It is worth pointing out several reasons why we desire to be able to just define new Monad instances whithout having to explicitly define instances for Functor and Applicative:

  • The idea of making Monad a subclass of Applicative was only discovered after many people had already used Monad in their programs. Therefore many existing programs already contain instance declarations for Monad as outlined above, so we would prefer not to have to change them just because the hierarchy has been refined to add extra functionality these existing programs don't use. This also applies to other hierachies in wide use at the moment, where changes have been proposed eg the Num hierarchy.
  • The implementation of (>>) in terms of (>>=) for Monad is much simpler than the default implementation provided by Applicative.
  • The example shows that sometimes the default implementation of a method depends on which subclass we are using, and so acts as a counterexample to the current assumption that default implementations can be provided in the class where the method is introduced.

Concrete proposal

  1. Class and instance declarations would allow method implementations to be given for any methods in the class or any ancestor class.
  2. Whenever an instance declaration is visible there would always be a full set of instance declarations for all ancestor classes, by supplementing the set of explicitly given instance declarations that are visible in a module by automatically generated implicit instance declarations.
  3. The most specific method implementation would always be chosen (ie prefer an explicit instance method over a class method and prefer a subclass method to a superclass method)
  4. Modules would only export explicit instance declarations

Clarifications

  • Separate compilation is still possible because all that's happening in the proposal is that the set of explicit instance declarations in scope in the module would be supplemented by a set of compiler-generated implicit instance declarations which are only visible in the module being compiled.

Implications

The most important implication of this proposal would be that the resolution of an overloaded method would depend on the instances in scope in the module where the method is called. Therefore overloading would need to be resolved before modules are conceptually merged together (especially important when considering whole program optimization), and in particular overloading of the body of an inlined function would need to be resolved using the module where the function was defined not the module where it is inlined.

Explicit import/export of instances

This is needed so that large programs can be built without fear of colliding instance declarations between different packages. A possible syntax could be:

    module M
         -- exported instances 
       ( instance Monad T
       , instance Functor (F a) hiding (Functor (F Int), Functor (F Char))
       , F(..)
       ) where

    import Foo (instance M (F a) hiding M (F String))

    data T a
    data F a b

where the context is elided because this isn't used in instance selection (at the moment).