[GHC] #8021: Multiple constraint classes - the alternative to superclass

#8021: Multiple constraint classes - the alternative to superclass -----------------------------+---------------------------------------------- Reporter: wvv | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- This is alternative to SuperClasses - multiple constraint Classes Now: {{{ class Monoid a where ... class Monad m => MonadPlus m where ... }}} It could be: {{{ class Monoid a where ... class Monad m => Monoid m where ... class Arrow c => Monoid c where ... foo :: Monad m => Monoid m => m a }}} all classes must have same functions with same kind. And if you wish to write superclass, it would be easy to write {{{ class BeforeNum a where .... class BeforeNum a => Num a where ... foo :: BeforeNum a => Num a => a }}} '''Backward compatibility''' If class have single constraint, you could write without it. If class have many constrains, 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 }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8021 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8021: Multiple constraint classes - the alternative to superclass -----------------------------+---------------------------------------------- Reporter: wvv | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by wvv): In other worlds, classes become instances of interfaces {{{ class Monoid a where ... <<==>> class () => Monoid a where ... class Monad m => Monoid m where ... }}} means something like {{{ interface Monoid class instance Monad m => Mononoid m where ... class instance () => Mononoid a where ... }}} Sure, interface is unwritten and compiler must create by itself and check class instances -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8021#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8021: Multiple constraint classes - the alternative to superclass -----------------------------+---------------------------------------------- Reporter: wvv | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by wvv): And you could allow to write classes as these: {{{ class interface Monoid where where -- Constructor (!) must be empty mempty :: * -- kinds only mappend :: * -> * -> * -- kinds only class Mononoid a where ... class Mononoid m where ... }}} Inside class interface constructor must be empty, because: {{{ () => Monoid a :: * Monad m => Monoid m :: * -> * Arrow c => Monoid c :: * -> * -> * }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8021#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8021: Multiple constraint classes - the alternative to superclass -----------------------------+---------------------------------------------- Reporter: wvv | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by wvv): I'm sorry, I've mistaken at the last comment {{{ class Mononoid a where ... class Mononoid m where ... }}} means {{{ class Mononoid a where ... class Monad m => Mononoid m where ... }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8021#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8021: Multiple constraint classes - the alternative to superclass -----------------------------+---------------------------------------------- Reporter: wvv | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by wvv): It new class Typeable work nice, interface could be rewritten as {{{ class interface Monoid (a :: k) where ... }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8021#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8021: Multiple constraint classes - the alternative to superclass -----------------------------+---------------------------------------------- Reporter: wvv | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.3 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by wvv): We already could define {{{ {-# LANGUAGE PolyKinds, FlexibleContexts, TypeFamilies #-} {-# LANGUAGE 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 rewrite this program: {{{ {-# LANGUAGE PolyKinds, FlexibleContexts, TypeFamilies #-} {-# LANGUAGE 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! -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/8021#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC