[Haskell-cafe] Newclasses

Stijn van Drongelen rhymoid
Fri Oct 4 21:14:12 UTC 2013


On Fri, Oct 4, 2013 at 10:31 PM, Wvv <vitea3v at rambler.ru> wrote:

> 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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131004/b67df03d/attachment.htm>



More information about the Haskell-Cafe mailing list