[Haskell-cafe] Newclasses

Wvv vitea3v
Thu Oct 3 19:15:05 UTC 2013


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.




More information about the Haskell-Cafe mailing list