Interfaces - the Golden Path of Haskell?

Wvv vitea3v at rambler.ru
Sat Jun 29 13:20:29 CEST 2013


This is fairly the same as 
http://hackage.haskell.org/trac/ghc/ticket/8021
but it's rewritten a little


Interfaces

Interface is a generalization of the class.

Now class become just *instances* of interface

For backward compatibility compiler should calculate interface by itself,
but it should allow to write interfaces to everybody (more detail at "Maybe
Problems").

 /-- it is calculated by the Compiler or is written directly/
 class interface Monoid (a :: k) where      /-- like Typeable/
    mempty  :: *            
    mappend :: * -> * -> *  


  class Monoid a where ... 

  class Monad m => Monoid m where ... 

  class Arrow c => Monoid c where ...


It is easy to use them with functions:

  foo :: (Monad m => Monoid m , Monad m ) => m a
  bar :: (Arrow c  => Monoid c, Arrow c) => c b a

These classes are open, you could lately add 
class MyClass c  => Monoid c where ...

We use like Typeable (a :: k)  because:

() => Monoid a      :: *
Monad m => Monoid m :: * -> *
Arrow c => Monoid c :: * -> * -> *

Backward compatibility


 If class have single constraint, you could write without it. 

 If class have many constraints, you could write without it, if it is empty
one. 

  bar :: MonadPlus m => m a  <<==>>  bar :: () => Monad m => MonadPlus m =>
m a 

  foo :: Monoid a => a          <<==>>  foo :: () => Monoid a => a

  baz :: Monad m => Monoid m => m a  <<==>> baz :: () => Monad m => Monoid m
=> m a


Better than superclasses


  we already have 
  class Num a where ...

But we wish to generalize it.
It's easy now, we just add:
 
  class Additive a where
     addplus = ...

  class Multiplicative a where
    multprod = ...

  class (Additive a, Multiplicative a) => Num a where
     (+) = addplus
     (*) = multprod

  foo :: (Additive a, Multiplicative a) => Num a => a -> a -> a


Maybe Problems


1)
     If we have already class 
     
     class Foo a where
        data F :: ...
        type S :: ...
        data family G ...

what interface do we have ?
Possible reply - no data in the interface.

2) What is the interface of Typeable ?
2.1) What is the interface of class with unwritten interface?

Possible reply - the same as class, so it is easy to Compiler.

3) 
 Misfeature - to allow write interface manually
 Why? You can't change it later.
 So, it must be deprecated from the beginning.



--
View this message in context: http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-tp5732208.html
Sent from the Haskell - Haskell-prime mailing list archive at Nabble.com.



More information about the Haskell-prime mailing list