[GHC] #8021: Multiple constraint classes - the alternative to superclass
GHC
ghc-devs at haskell.org
Sat Jul 6 20:19:08 CEST 2013
#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
More information about the ghc-tickets
mailing list