
"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.

Hi! Your first two cases will be fixed in 7.10, as Applicative finally becomes a superclass of Monad. I haven't really looked at your third case, so I can't comment on that. Your fourth case is something I'd really like to see solved properly (*together* with a better record system), but as you say, it could be solved separately. Also, I don't see why it would be a misfeature to have Eq as a superclass of Ord, or Functor as a superclass of Applicative. -Stijn

> Your first two cases will be fixed in 7.10, as Applicative finally becomes a superclass of Monad. Sure, newclassses not about Applicative and Monads only. This question is more wider. Must Apply be a superclass of Bind? Must Bind be a superclass of Monad? So, must Monad has 2 superclasses at once: Bind and Applicative? Must Semigroupoids be a superclass of Category? Must Category be a superclass of Arrow? With newclasses we could write empty instances to provide correct functional dependencies: instance ArrCategory MyArrow instance CatSemigroupoids MyCategory instance MBind MyMonad instance MApply MyMonad instance MApplicative MyMonad instance MFunctor MyMonad > Also, I don't see why it would be a misfeature to have Eq as a superclass > of Ord, or Functor as a superclass of Applicative. I see 2 reasons: 1) class functions in reality don't depend of superclass functions 2) Haskell can't check if superclass instance is correspond with class laws -- View this message in context: http://haskell.1045720.n5.nabble.com/Newclasses-tp5737596p5737625.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Thu, Oct 3, 2013 at 8:16 AM, Wvvwrote: > > Your first two cases will be fixed in 7.10, as Applicative finally > becomes > a superclass of Monad. > > Sure, newclassses not about Applicative and Monads only. > This question is more wider. > > Must Apply be a superclass of Bind? > Must Bind be a superclass of Monad? > So, must Monad has 2 superclasses at once: Bind and Applicative? > > Must Semigroupoids be a superclass of Category? > Must Category be a superclass of Arrow? There is no theoretical problem here, just a practical one. It would be resolved by solving your 4th problem, for which you don't need newclasses. Consider: {-# LANGUAGE ConstraintKinds #-} class Functor f where { fmap :: (a -> b) -> f a -> f b } class Functor f => Apply f where { (<*>) :: f (a -> b) -> f a -> f b } class Apply f => Applicative f where { pure :: a -> f a } class Apply f => Bind f where { (=<<) :: (a -> f b) -> f a -> f b } type Monad f = (Applicative f, Bind f) return :: Monad f => a -> f a return = pure I might have made some mistakes in the exact hierarchy, but something like this should work. There are no problems with having hierarchies like this, as far as I'm aware. The current problem is that nobody wants to use this hierarchy: to get a Monad instance, you have to write four separate instances for your type. What would be nicer is a feature (ConstraintSynonymInstances?) where something like this can be written: instance (Functor Maybe, Apply Maybe, Monad Maybe) where fmap _ Nothing = Nothing fmap f (Just x) = Just (f x) Just f <*> Just x = Just (f x) _ <*> _ = Nothing pure = Just f =<< Just x = f x _ =<< Nothing = Nothing This would be sugar for instance Functor Maybe where { fmap = ... } instance Apply Maybe where { (<*>) = ... } instance Monad Maybe where { pure = ... ; (=<<) = ... } and the last would be sugar for instance Applicative Maybe where { pure = ... } instance Bind Maybe where { (=<<) = ... } You don't need any new keywords for this, because the above does not conflict with the existing rules for instance declarations. > Also, I don't see why it would be a misfeature to have Eq as a superclass > > of Ord, or Functor as a superclass of Applicative. > I see 2 reasons: > 1) class functions in reality don't depend of superclass functions > 2) Haskell can't check if superclass instance is correspond with class laws Again, I don't see why that makes it a misfeature.

Yes, multi-class instances allow us write type Monad a = (Applicative a, Bind a) But at least 1 issue remains: Applicative : pure; Monad: return Bind : (>-); Monad: (>>=) With MultiClassInstances we could write only instance Monad MyMonad where { pure= ...; (>-)= ...} But we don't want to break the existent code. Fortunately, an easy extension FunctionSynonyms could help us: type return = pure -- this allow us to use 'return' instead of 'pure' in instances type (>>=) = (>-) -- this allow us to use '(>>=)' instead of '(>-)' in instances 2) Still remains issue with several default instances, like 'Generic a => ToJSON a' and 'Data a => ToJSON a', which we can't unite to 1 instance 3) If devs of library don't want to change the behavior, (for example divide Monad to Applicative and Bind), but we still want easy connection to that class, newclasses is our choice! Yes, this solution is good! Very nice! I like it! I should name it solution from derivatives. From bottom to top. We have only independent classes and unite them with "types". Newclasses solve same problem in integral way. From top to bottom. Instead of having independent little classes, it allow to have big classes with dependences, which are written in newclasses, and they allow to connect easy to any dependent class. newclass Bind a => Monad a => BMonad a where { (>>=) = (>>-) } newclass Applicative a => Monad a => ApMonad a where { return = pure } newclass (BMonad a, ApMonad a) => BApMonad a --empty type ApBMonad = BApMonad --then connect these classes: instance Bind MyDataAB where { (>-) = ...} instance Applicative MyDataAB where { pure = ... ; (<*>) = ...} instance ApBMonad MyDataAB --empty --or these instance Monad MyDataM where {return= ... ; (>>=) = ...} instance MBind MyDataM --empty instance MApply MyDataM --empty instance MApplicative MyDataM --empty instance MFunctor MyDataM --empty If Haskell add MultiClassInstances + FunctionSynonyms, or Newclasses, or both of them, Haskell would be the best language in nearest future!!! About the "misfeature". If class is independent of superclass functions and can't check dependence's laws, why does it order to have instances of unnecessary class? Stijn van Drongelen wrote > On Thu, Oct 3, 2013 at 8:16 AM, Wvv < > vitea3v@ > > wrote: > >> > Your first two cases will be fixed in 7.10, as Applicative finally >> becomes >> a superclass of Monad. >> >> Sure, newclassses not about Applicative and Monads only. >> This question is more wider. >> >> Must Apply be a superclass of Bind? >> Must Bind be a superclass of Monad? >> So, must Monad has 2 superclasses at once: Bind and Applicative? >> >> Must Semigroupoids be a superclass of Category? >> Must Category be a superclass of Arrow? > > > There is no theoretical problem here, just a practical one. It would be > resolved by solving your 4th problem, for which you don't need newclasses. > Consider: > > {-# LANGUAGE ConstraintKinds #-} > class Functor f where { fmap :: (a -> b) -> f a -> f b } > class Functor f => Apply f where { (<*>) :: f (a -> b) -> f a -> f b } > class Apply f => Applicative f where { pure :: a -> f a } > class Apply f => Bind f where { (=<<) :: (a -> f b) -> f a -> f b } > > type Monad f = (Applicative f, Bind f) > return :: Monad f => a -> f a > return = pure > > I might have made some mistakes in the exact hierarchy, but something like > this should work. There are no problems with having hierarchies like this, > as far as I'm aware. > > The current problem is that nobody wants to use this hierarchy: to get a > Monad instance, you have to write four separate instances for your type. > What would be nicer is a feature (ConstraintSynonymInstances?) where > something like this can be written: > > instance (Functor Maybe, Apply Maybe, Monad Maybe) where > fmap _ Nothing = Nothing > fmap f (Just x) = Just (f x) > > Just f <*> Just x = Just (f x) > _ <*> _ = Nothing > > pure = Just > > f =<< Just x = f x > _ =<< Nothing = Nothing > > This would be sugar for > > instance Functor Maybe where { fmap = ... } > instance Apply Maybe where { (<*>) = ... } > instance Monad Maybe where { pure = ... ; (=<<) = ... } > > and the last would be sugar for > > instance Applicative Maybe where { pure = ... } > instance Bind Maybe where { (=<<) = ... } > > You don't need any new keywords for this, because the above does not > conflict with the existing rules for instance declarations. > > > Also, I don't see why it would be a misfeature to have Eq as a > superclass >> > of Ord, or Functor as a superclass of Applicative. >> I see 2 reasons: >> 1) class functions in reality don't depend of superclass functions >> 2) Haskell can't check if superclass instance is correspond with class >> laws > > > Again, I don't see why that makes it a misfeature. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@ > http://www.haskell.org/mailman/listinfo/haskell-cafe -- View this message in context: http://haskell.1045720.n5.nabble.com/Newclasses-tp5737596p5737705.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

I don't really understand what a "newclass" is supposed to be.
On Thu, Oct 3, 2013 at 2:15 PM, Wvv
newclass Bind a => Monad a => BMonad a where { (>>=) = (>>-) }
I think this means that `BMonad` is supposed to be a new class that has both Bind and Monad in scope, the same as class (Bind a, Monad a) => BMonad a except that the Monad instance's (>>=) is replaced by (>>-). If that's what "newclass" means, it seems absolutely pointless. Does it instead mean that one could write instance Bind MyType where instance BMonad MyType

Apologies, that wasn't finished. I meant to say, does it mean that by
writing a BMonad instance a Monad instance would be automatically
generated? If so, that seems like it would cause conflicts in many cases.
Regardless, I think "newclass" needs to be better specified if you want
other people to be able to support it.
On Thu, Oct 3, 2013 at 7:53 PM, John Lato
I don't really understand what a "newclass" is supposed to be.
On Thu, Oct 3, 2013 at 2:15 PM, Wvv
wrote: newclass Bind a => Monad a => BMonad a where { (>>=) = (>>-) }
I think this means that `BMonad` is supposed to be a new class that has both Bind and Monad in scope, the same as
class (Bind a, Monad a) => BMonad a
except that the Monad instance's (>>=) is replaced by (>>-).
If that's what "newclass" means, it seems absolutely pointless.
Does it instead mean that one could write
instance Bind MyType where
instance BMonad MyType

Newclasses are something like instances, but out of scope. In a baggage. We don't use them for interfere their functions. This why newclasses never overlap each other and between them and any instances. We use newclasses to plug-in/connect to any related class or combine data Replying to you question, yes, instance of newclass desugar to instance of class: instance BMonad MyBind where {return= ...} desugar into instance Monad MyBind where {return= ...; (>>=) = (>>-)} We already have too many classes: look at Edward Kmett http://hackage.haskell.org/package/semigroupoids 13 dependent classes (from Foldable to MonadPlus) http://hackage.haskell.org/package/category-extras 30-60 dependent class http://hackage.haskell.org/package/lens 11 dependent classes We can't divide all classes to atimic ones. I do not want to implement all depended class instances, even of atomic, if I want to work with hight class only. But I want easy connection with any related class! And newclasses solve this situation. Also in reality we have several realizations of same class/compose data and we want to mix them for better realizations. Newclasses allows switch them as engines! Easy. Main purpose of newclasses is to make instances as minimal as possible. In many cases empty. About newclass and compose data, we can do next: newclass Foo [a] => FooList a where {containerMainipulation=...} newclass Foo (Set a) => FooSet a where {containerMainipulation=...} newclass Foo (Sequence a) => FooSeq a where {containerMainipulation=...} so now I can switch any container of my data, changing only name of newclass: instance FooList MyData where {dataMainipulation=...} Or let I have an MyArrow data. And I need some semigroupoid manipulations. I just write instance ArrSemigroupoid MyArrow --empty that's all, I plug-in, let's just use semigroupoids functions! Or I have MyMonad and I want some Functor, so I just plug-in: instance MFunctor MyMonad --empty that's all. I also need some Applicative! Easy: instance MApplicative MyMonad --empty again done! About conflicts, I don't understand a bit. Which ones? We catch Overlapped instances or even Incoherent instances at once we add both newclass instances of the same class. John Lato-2 wrote
I meant to say, does it mean that by writing a BMonad instance a Monad instance would be automatically generated? If so, that seems like it would cause conflicts in many cases. Regardless, I think "newclass" needs to be better specified if you want other people to be able to support it.
On Thu, Oct 3, 2013 at 7:53 PM, John Lato <
jwlato@
> wrote:
I don't really understand what a "newclass" is supposed to be.
On Thu, Oct 3, 2013 at 2:15 PM, Wvv <
vitea3v@
> wrote:
newclass Bind a => Monad a => BMonad a where { (>>=) = (>>-) }
I think this means that `BMonad` is supposed to be a new class that has both Bind and Monad in scope, the same as
class (Bind a, Monad a) => BMonad a
except that the Monad instance's (>>=) is replaced by (>>-).
If that's what "newclass" means, it seems absolutely pointless.
Does it instead mean that one could write
instance Bind MyType where
instance BMonad MyType
_______________________________________________ Haskell-Cafe mailing list
Haskell-Cafe@
-- View this message in context: http://haskell.1045720.n5.nabble.com/Newclasses-tp5737596p5737792.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Fri, Oct 4, 2013 at 10:31 PM, Wvv
Newclasses are something like instances, but out of scope. In a baggage.
So under the hood of GHC, newclasses would be partially filled in dictionaries. We already have too many classes: (...)
We can't divide all classes to atimic ones.
As you have seen, we can. As you also see, it is a little impractical. Main purpose of newclasses is to make instances as minimal as possible. In
many cases empty.
About newclass and compose data, we can do next:
newclass Foo [a] => FooList a where {containerMainipulation=...}
newclass Foo (Set a) => FooSet a where {containerMainipulation=...}
newclass Foo (Sequence a) => FooSeq a where {containerMainipulation=...}
so now I can switch any container of my data, changing only name of newclass:
instance FooList MyData where {dataMainipulation=...}
You can already solve that in Haskell 98: class Foo2 f where { containerManipulation = ... } instance Foo2 [] where { ... } instance Foo2 Set where { ... } instance Foo2 Sequence where { ... } class (Foo2 f) => Foo1 f a where { dataManipulation = ... } Or even: class Foo' a where { dataManipulation' = ... } dataManipulation = dataManipulation' yourDefaultContainerManipulation Remember: the only special things about type classes is that they are types that can/must be implicit. You can (almost?) always replace them by explicit parameters. Or let I have an MyArrow data. And I need some semigroupoid manipulations.
I just write
instance ArrSemigroupoid MyArrow --empty
that's all, I plug-in, let's just use semigroupoids functions!
Or I have MyMonad and I want some Functor, so I just plug-in:
instance MFunctor MyMonad --empty
that's all. I also need some Applicative! Easy:
instance MApplicative MyMonad --empty again
done!
Let's see how many lines of code this costs in Haskell 98: instance Monad MyMonad where { ... } instance Functor MyMonad where fmap = liftM instance Applicative MyMonad where pure = return (<*>) = ap Only three lines more, and they're readable. I think newclasses are not solving the existing problems, as you're only removing three well-understood lines of code in the above example, while people have to look up what you mean by MFunctor and MApplicative. I think default superclass instances are a much better idea, or alternatively, the ConstraintSynonymInstances I previously mentioned (but not both -- they'll probably bite each other). -Stijn

Stijn van Drongelen wrote
On Fri, Oct 4, 2013 at 10:31 PM, Wvv <
vitea3v@
> wrote:
About newclass and compose data, we can do next:
newclass Foo [a] => FooList a where {containerMainipulation=...}
newclass Foo (Set a) => FooSet a where {containerMainipulation=...}
newclass Foo (Sequence a) => FooSeq a where {containerMainipulation=...}
so now I can switch any container of my data, changing only name of newclass:
instance FooList MyData where {dataMainipulation=...}
You can already solve that in Haskell 98:
class Foo2 f where { containerManipulation = ... } instance Foo2 [] where { ... } instance Foo2 Set where { ... } instance Foo2 Sequence where { ... }
class (Foo2 f) => Foo1 f a where { dataManipulation = ... }
Or even:
class Foo' a where { dataManipulation' = ... } dataManipulation = dataManipulation' yourDefaultContainerManipulation
Yes, I agree, use newclasses for composite data is an additional, secondary feature. Haskell has huge infrastructure of data to use alternative ways instead using newclasses this way. Stijn van Drongelen wrote
On Fri, Oct 4, 2013 at 10:31 PM, Wvv <
vitea3v@
> wrote:
Let's see how many lines of code this costs in Haskell 98:
instance Monad MyMonad where { ... } instance Functor MyMonad where fmap = liftM instance Applicative MyMonad where pure = return (<*>) = ap
Only three lines more, and they're readable.
I see, we are looking to the same situation from different angles. I try to show you why I think my point of view is important. 2 situations: first is more practical, second is more philosophical. (1) we have several libraries with lenses and lens-looking like libraries. Why is the main popularity going to Kmett's library? My answer: easy connection: just add one line " makeLens MyRecord'' " and we already could use all their abilities. Why Kmett's library of JSON is so popular. Sure, it more quicker, but what is the main reason? My answer: easy connection. Why Pipes, Streams, Conduit, .... are not as super-popular as they could be? They have very powerful abilities. You need time not only for studying how this library works, but also how to switch your data to library functions. If you need to work with ... RMonad or MonadDatabase or something like this, do you always know how to switch your data on? (2) Let I have a lamp and I wish to switch it on. So, I say, I want to have a plug. But you argue: this isn't necessary: you take 3 wires, green one you contact here, blue one contact here, and finally, brown one contact there! Easy! Ok, now I wish to connect computer with iPhone. You say: take 12 wires , pins-scheme, .... But I want USB-30pin cable. Newclasses are those connectors-plugs and adapters. Deriving are those plugs. Generic instances and Data instances are those plugs. Newclasses are something like deriving, but much-much flexible and more universal (sure, we can't replace deriving with newclasses). If I have a Data which has an instance of Foo and I want to switch it to class Bar, and I have 2 newclasses: Foo2Tmp and Tmp2Bar, I do the next: instance Foo2Tmp MyData instance Tmp2Bar MyData done! or much simpler if I have Foo2Bar newclass: instance Foo2Bar MyData I do not care how easy or complex those instances I could write without newclasses. My aim is not to connect, but use abilities, which I take after connection. And newclass is amazing tool for easy connection between classes. -- View this message in context: http://haskell.1045720.n5.nabble.com/Newclasses-tp5737596p5737833.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
participants (3)
-
John Lato
-
Stijn van Drongelen
-
Wvv