"Newclasses" are not a new vision of classes! Not at all! Newclasses could elegant solve several instance problems!
1) we want to have "partly applied instances", like Parent2Child: Parent a => Child a like instance Applicative m => Monad m where return = pure -- we won't define here (>>=) 2) we want to have superclass' instances, like Child2Parent: Child a => Parent a like instance Monad m => Applicative m where pure = return (<*>) = ap 3) we want to have default instances outside of class and as many as possible, not the only one. like class Foo a where foo :: ... default foo :: ... foo = ... 4) we want to have multi-class instances to separate (or unite) classes like type Stringy a = (Show a, Read a) instance Stringy SomeData where read = ... show = ... (4)th problem we could solve separately, but maybe it isn't easy enough to do such de-sugaring, and it could much easier to add them in newclasses. (3)rd problem is solved partly, but not in universal way, non-flexible and a bit ugly. (2)nd problem is solved, but it is mostly impossible to use them and it is not recommend to use it for overlapping and incoherent issues. (1)st problem is unsolved at all (partly, it is possible to make depended classes, but checker don't check if we implement parent classes). This is a compose proposal. Newclasses solve these problems at once! As newtype is a data looking like a type, same newclass is looking like a class, but is mostly an instance! Mostly, but not full. To best understanding what "newclasses" is, let's look at (1)st problem: -- we wish to write -- instance Applicative m => Monad m where -- return = pure -- we write "newclass" instead of "instance" -- add "=>" and giving a name to newclass like a class -- this is not instance, so newclass can't overlap with any instance newclass (Applicative m) => Monad m => ApMonad m where return = pure data D a .... instance Applicative D where pure = ... (<*>) = ... -- creating instances from newclass is intuitive -- we implement here Monad class, not "ApMonad"; ApMonad is a just newclass instance ApMonad D where -- we already have 'return = pure', so we define only (>>=) (>>=) = ... What do we see here? Newclass looks like class, but it's mostly an instance! Newclass: Grammar: newclass constraint => Parent a => NewClassName a where ... As class, newclass has a name, which is unique and can't conflict with any other newclass or class names. As class, methods of newclass could be empty or implemented. As class, methods of newclass are not use in function inference. As class we can make an instance of newclasses and overwrite any of his functions! But, instance of newclass IS an instance of the parent (!)class! So, newclasses is like a de-sugaring. As instance, newclass contains only parents methods! On contrary to instancess, we don't use newclasse directly, it only help us to create instances. If we allow for newclass to be as Parent not only classes, but newclasses, then newclass can't be recursive: neither of his (Grand)Parent could be he by himself. If we allow for newclass muliple Parents, we solve (4)th problem too. Examples: We have: class Functor f where fmap :: (a -> b) -> f a -> f b class Applicative f where -- without "Functor f =>", this is a misfeature pure :: a -> f a (<*>) :: f (a -> b) -> f a -> f b class Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b class Ord' a where -- without "Eq a =>", this is a misfeature ... compare a b -- not as in Prelude | a < b = LT | a > b = GT | otherwise = EQ (1)st, Parent2Child: Common pattern to write newclass like: newclass Parent a => Child a => ParChild a where ... Examples: newclass (Applicative m) => Monad m => ApMonad m where return = pure data C1 a ... instance Applicative C1 where pure = ... (<*>) = ... instance ApMonad C1 where -- return is already defined (>>=) = ... -- newclass (Ord' a) => Eq a => OEq a where a == b = case compare a b of EQ -> True _ -> False data C2 ... instance Ord' C2 where (>) = ... (<) = ... instance OEq C2 -- empty instance for Eq (2)nd, Child2Parrent: Common pattern to write newclass like: newclass Child a => Parent a => ChParent a where ... Examples: newclass (Eq a) => Ord' a => Ord a where compare a b | a == b = EQ | a >= b = GT | otherwise = LT data C3 ... instance Eq C3 where (==) = ... instance Ord C3 where -- Ord with much effective `compare`, than Ord' (>) = ... (<) = ... -- newclass Monad m => Applicative m => MApplicative m where pure = return (<*>) = ap data C4 a ... instance Monad C4 where return = ... (>>=) = ... instance MApplicative C4 -- empty, everything is already defined ! -- newclass Monad m => Functor m => MFunctor m where fmap = liftM newclass Applicative f => Functor f => ApFunctor f where fmap f x = pure f <*> x data C5 a ... instance Applicative C5 where pure = ... (<*>) = ... instance ApMonad C5 where (>>=) = ... -- without return instance MFunctor C5 --(!) or instance ApFunctor C5 --(!!!) but not both (3)rd, default instances: Common pattern to write newclass like: newclass GenericConstraint a => Class a => GNewclass a where ... Examples: class ToJSON a where toJSON :: a -> Value newclass (Generic a, GToJSON (Rep a)) => ToJSON a => GenToJSON a where toJSON = genericToJSON defaultOptions newclass (Data a) => ToJSON a => DataToJSON a where toJSON = dataToJSON defaultOptions data C6 ... deriving (Generic, Data) -- don't forget to create an empty instance! instance GenToJSON C6 --(!) or instance DataToJSON C6 --(!!!) but not both (4)th, multi-class instances Common pattern to write newclass: newclass (Class1 a, Class2 a, Class3 a)=> Newclass a where ... Examples: newclass (Read a, Show a) => Stringy a -- without where data C7 ... instance Stringy C7 where read = ... show = ... -- class MinBounded a where minBound :: a class MaxBounded a where maxBound :: a newclass (MinBounded a, MaxBounded a) => Bounded a -- class Additive a where (+) :: a -> a -> a class Additive a => AdditiveZero a where zero :: a class Mulipicative a where (*) :: a -> a -> a class Mulipicative a => MulipicativeOne a where one :: a newclass (Additive a, Mulipicative a, Substravive a, FromInteger a) => Num a -- without where newclass (AdditiveZero a, MulipicativeOne a, Substravive a, FromInteger a) => NumFull a -- Benefits: - "newclass" is a very powerful tool - it is universal solution without extra assumptions! - solve 4 big problems with instances - it is a Huge step - it is a step forward, not aside - it is developing function's muscles to Haskell Disadvantages: - new reserved word "newclass" - with Child2Parrent problem it is needed to write empty instances - main difficulty - it is not easy to implement this extension! Newclasses could also help to reorganize some Prelude classes, like Ord, Applicative, Functor, Bound, Num, ... What do you think of this proposal? You opinion is important and significant! Let's help to develop Haskell together! Do you like "newclasses"? Do you want to use them? Do you think newclasses are appropriate solution for written problems? Could newclasses help to resolve some other problems? Are they useless? Do you see huge difficulties of implementation? Do you have more elegant ideas, which correspondent with newclasses? If it is not clear enough, I write more clearly. Any feedback is welcome! -- View this message in context: http://haskell.1045720.n5.nabble.com/Newclasses-tp5737596.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe