Interfaces - the Golden Path of Haskell?

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-t... Sent from the Haskell - Haskell-prime mailing list archive at Nabble.com.

Wvv wrote:
class Monoid a where ...
class Monad m => Monoid m where ...
This is a kind error. The m in Monoid has kind *, while the one in Monad has kind * -> *. I suggest you (try to) rewrite your proposal to eliminate these kind errors before any further elaboration. Cheers -- Ben Franksen () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachm€nts

We already could write and compile next code: {-# LANGUAGE PolyKinds, FlexibleContexts, TypeFamilies #-} {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} class Monoid (a :: k) where type Pr a :: * mempty :: PA a mappend :: Pr a -> Pr a -> Pr a instance Monoid [b] where type Pr [b] = [b] mempty = [] mappend = (++) instance (Monad m, MonadPlus m) => Monoid ( m :: * -> * ) where type Pr m = m Int -- Unfortunally, we can't write now type Pr m = forall b. m b --Illegal polymorphic or qualified type: forall b. m b mempty = mzero mappend = mplus This code is already valid. But we can't use any written instance at all, the ambiguity problem. Wvv 29 / 06 / 2013 17:39:25 user Ben Franksen [via Haskell] (ml-node+s1045720n5732210h49@n5.nabble.com) wrote: This is a kind error. The m in Monoid has kind *, while the one in Monad has kind * -> *. I suggest you (try to) rewrite your proposal to eliminate these kind errors before any further elaboration. Cheers -- Ben Franksen () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachm€nts _______________________________________________ Haskell-prime mailing list [hidden email] http://www.haskell.org/mailman/listinfo/haskell-prime ---------------------------------------------------------------------------- If you reply to this email, your message will be added to the discussion below:http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-t... To unsubscribe from Interfaces - the Golden Path of Haskell?, click here. NAML -- View this message in context: http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-t... Sent from the Haskell - Haskell-prime mailing list archive at Nabble.com.

We already could define {-# LANGUAGE PolyKinds, FlexibleContexts, TypeFamilies, FlexibleInstances, UndecidableInstances, RankNTypes #-} module Monoids where import Control.Monad import Control.Arrow class Monoid (a :: k) where type PrE a :: * mempty :: PrE a mappend :: PrE a -> PrE a -> PrE a instance Monoid [b] where type PrE [b] = [b] mempty = [] mappend = (++) instance (Monad m, MonadPlus m) => Monoid ( m b ) where type PrE (m b) = m b mempty = mzero mappend = mplus instance (Arrow a, ArrowPlus a, ArrowZero a) => Monoid ( a b c ) where type PrE (a b c) = a b c mempty = zeroArrow mappend = (<+>) And this program is valid. We can't use it at all, but as we see, the GHC is already has most features to implement -XClassInterfaces extension. I suggest to write this program like this: {-# LANGUAGE ClassInterfaces, PolyKinds, FlexibleContexts, TypeFamilies, FlexibleInstances, UndecidableInstances, RankNTypes #-} module Monoids where import Control.Monad import Control.Arrow class interface Monoid (a :: k) where type PrE a :: * mempty :: PrE a mappend :: PrE a -> PrE a -> PrE a class Monoid [b] where type PrE [b] = [b] mempty = [] mappend = (++) class (Monad m, MonadPlus m) => Monoid (forall b. m b ) where type PrE (m b) = m b mempty = mzero mappend = mplus class (Arrow a, ArrowPlus a, ArrowZero a) => Monoid (forall b, c. a b c) where type PrE (a b c) = a b c mempty = zeroArrow mappend = (<+>) that's all! -- View this message in context: http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-t... Sent from the Haskell - Haskell-prime mailing list archive at Nabble.com.

And this is only tip of the iceberg. Now we have discussion about (Monad m) vs. (Functor m => Monad m). With class interfaces it is not an option: we have them both(!!!) {{{ class Monad m where ... class Functor m => Applicative m => Monad m where .. }}} Let's see how it could work: We have {{{ class Num a where (+), (*) :: a -> a -> a (-) :: a -> a -> a negate :: a -> a fromInteger :: Integer -> a }}} Let we also have {{{ class Additive a where plus :: a -> a -> a zero :: a class Additive a => AdditiveNegation a where minus :: a -> a -> a negation :: a -> a x `minus` y = x `plus` negation y class Multiplicative a where multiply :: a -> a -> a one :: a class FromInteger a where fromInteger' :: Integer -> a }}} Now we wish to unite both of them For example, we could also define next: {{{ class (Additive a, Additive a => AdditiveNegation a, Multiplicative a, FromInteger a) => Num a where (+) = plus (*) = multiply (-) = minus negate = negation fromInteger = fromInteger' class (Num a) => Additive a where plus = (+) zero :: a default zero :: () => Additive a => a default zero = zero class (Num a) => AdditiveNegation a where minus = (-) negation = negate class (Num a) => Multiplicative a where multiply = (*) one :: a default one :: () => Multiplicative a => a default one = one class (Num a) => FromInteger a where fromInteger' = fromInteger }}} Wvv -- View this message in context: http://haskell.1045720.n5.nabble.com/Interfaces-the-Golden-Path-of-Haskell-t... Sent from the Haskell - Haskell-prime mailing list archive at Nabble.com.
participants (2)
-
Ben Franksen
-
Wvv