[Haskell-cafe] Newclasses

Stijn van Drongelen rhymoid
Thu Oct 3 09:45:48 UTC 2013


On Thu, Oct 3, 2013 at 8:16 AM, Wvv <vitea3v at rambler.ru> 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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131003/33f2dac1/attachment.htm>



More information about the Haskell-Cafe mailing list