#788: Implement class aliases and/or constraint synonyms
---------------------------+------------------------------------------------
  Reporter:  simonpj       |           Type:  feature request        
    Status:  new           |       Priority:  normal                 
 Milestone:  _|_           |      Component:  Compiler (Type checker)
   Version:                |       Keywords:                         
  Testcase:  N/A           |      Blockedby:                         
Difficulty:  Unknown       |             Os:  Unknown/Multiple       
  Blocking:                |   Architecture:  Unknown/Multiple       
   Failure:  None/Unknown  |  
---------------------------+------------------------------------------------

Comment(by batterseapower):

 Superclass defaulting is another alternative. This is a proposal that has
 come up again recently on the mailing list. It is attractive because it
 would allow us to refactor class hierarchies (such as the infamous Monad)
 in a backwards-compatible manner.

 The proposal would allow code like this:

 {{{
 class Functor f where
     fmap :: (a -> b) -> f a -> f b

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

     fmap f mx = mx >>= (return . f)
 }}}

 The change is that class declarations can include default methods not only
 for methods of that class, but also any of its superclasses. This allows
 us to add superclasses to an existing class but provide defaults for their
 methods. These defaults will be used to manufacture a superclass instance
 (like Functor) if one is not available at the point where we declare a
 class instance (like Monad), thus - mostly - avoiding breakage of user
 code.

 Of course, user code will still break if we have orphan instances. For
 example this user code will break if we refactor Monad in this way:

 {{{
 module A where

 instance Monad AType where
   ...
 }}}

 With:

 {{{
 module B where
 import A

 instance Functor AType where
   ...
 }}}

 Because the orphan Functor AType instance will not be available in module
 A, so superclass defaulting will manufacture a Functor instance there and
 then, which then overlaps with the one from module B. But abusers of
 orphans deserve what they get :-)

 The first major problem I can think of (as with class aliases) is with
 code like this:

 {{{
 class Foo a where
     foo :: a -> String

 class (Foo a, Foo b) => Bar a b where
     bar :: Either a b -> String

     foo = bar . Left

     foo = bar . Right
 }}}

 How should this be interpreted? It is clear that the user intended to
 provide superclass defaults for *both* Foo superclasses, but if we just
 parse it looks like a single foo method with two right hand sides. Even if
 we parse it as two different declarations then we have to use information
 about the inferred type of each default to decide which superclass
 instance it should contribute to.

 One option would be to say you can only write one superclass default for
 any given superclass method, which lets us do Monads but defers treatment
 of the hard cases.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/788#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to