[Haskell-cafe] Proposal: RankedInstances

Wvv vitea3v at rambler.ru
Fri Sep 27 01:37:56 CEST 2013


The main power of Haskell is on instances.
But Haskell instances system work fine with lower number of instances (rare
instances).
But we want hight density of instances!
If we wish to have more selective instances we use `OverlappingInstances`
(which are desined in a poor way)  and if we still have too many instances
we use `IncoherentInstances`.

~~`RankedInstances` extension ~~

I suggest simple `RankedInstances` extension.
We use it (!)before OverlappingInstances (it must include
`RankedInstances`), and in many cases instead of.

This extension is easy to implement and it give us a lot of new
possibilities and instruments.

Now the system of instances is flat, and compiler takes all of them and
check if only 1 match. If it is not(less or more than) - compiler trow an
error.

I suggest to add rankings, so compiler
* compiler set N=0
* took all N-ranked instances and 
 ** try to find only one match instance.
 *** If it found 1 - this is RESULT: needed instance, 
 *** If it found many instances - still throw an error 
 ******* (then we use `OverlappingInstances` to resolve this)
 *** If compiler found NO instances, compiler set N=N+1 and repeat
* If N=MaxRank and still no matches compiler throw an error

~~How to add a rank~~
I suggest next grammar:

  {-# LANGUAGE RankedInstances #-}

  instance rank 1. C a => D a where ...


  instance           C2 a => E a where ...  
  <<==>> 
  instance rank 0. C2 a => E a where ...

So, all written instances(without ranking) are 0-ranked instances.

Backward compatibility => without -XRankedInstances all instances with rank
n, where n >0 - are not exported

~Example~
1)
  instance rank 1. C Int a     where ...   -- (A)
  instance           C a   Bool  where ...   -- (B) rank 0
1+)
  instance rank 1. C Int a     where ...   -- (A)
  instance rank 1. C a   Bool  where ...   -- (B)  
  instance           C Int Bool  where ...   -- (C) rank 0
  
2)
  instance rank 1. C Int [a]  where ...  -- (C)
  instance         C Int [Int]  where ...  -- (D)

As we see, all instances are unambiguous!

~~ Rank Scale~~

It is for discussion, I see this like:
0           - default
1 ..9      - user free (without fear to overlap with devs instances)
10 .. 14  - Generic
15 ..      - superclass' instances

~~ Higher Rank instances~~
We don't need to use `default` inside of class:

  instance rank 10. (Generic a, GToJSON (Rep a)) => ToJSON a where
    toJSON = genericToJSON defaultOptions

We could add superclass' instances now, something like these:

  instance rank 15. Monad m => Applicative m where 
    pure  = return 
    (<*>) = ap 
 
  instance rank 16. Monad m => Functor m where 
    fmap = liftM  
	
  instance rank 17. Applicative m => Functor m where 
    fmap f x = pure f <*> x

~~Inherit mechanism~~

What do if we want to use any proposed instance, not in the rank order ?
For example we have data, which is Monad and Applicative, but not a Functor.
We'll use automatically "instance rank 16. Monad m => Functor m", but not
"instance rank 17. Applicative m => Functor m" .
But we wish to use the last one. We need to create a new instance and
inherit the behavior of needed instance


  data D a ....

  instance Monad D where ...
  instance Applicative D where ...

  instance rank 1. Functor D inherit (D ~ m)
	instance Applicative m => Functor m

  foo = ... fmap

So, in this case we'll use `fmap` as Applicative Functor.

Inherit mechanism defaulting :

   instance  C a => D a where ...
   <<==>>
   instance  C a => D a inherit (a ~ b) class D b where

~~ "As" pattern in RankedInstances~~

Now we add "as" pattern and rewrite both of our instances:

  instance rank 17. Applicative m => ApFunctor at Functor m where 
    fmap f x = pure f <*> x
	
  instance ApFunctor D         --by the way 0-ranked

Wow!!! It is simple, safe and looks nicer! 

~~Partly Applied Instances~~

We describe a situation when we write a child class and want automatically
get access to parent's classes.
But sometimes we need to use already defined parent classes to describe
children classes

We CANNOT do next:

  instance rank 20. (Functor m, Applicative m) => Monad m where 
    ma >> mb = (fmap (const id) ma) `apply` mb

  instance rank 21. Applicative m => Monad m where
    ma >> mb = (pure (const id) <*> ma) `apply` mb	

Because if we define 

  data D a ...

  instance Functor D ...
  instance Applicative D ...

  D a >>= D b  -- this will compiler, but we have no full applied
MonadInstance

How to resolve this?

I suggest to add one reserved world "newclass" (as an analog of newtype)


--instance (Functor m, Applicative m) => FAMonad at Monad m where 
newclass (Functor m, Applicative m) => FAMonad at Monad m where 
    ma >> mb = (fmap (const id) ma) `apply` mb

--instance Applicative m => AMonad at Monad m where
newclass (Applicative m) => AMonad at Monad m where 
    ma >> mb = (pure (const id) <*> ma) `apply` mb

The "newclass" is just an instance, but guarded - compiler did count it when
it try to match
So, now next throw an error: D a >>= D b

And we have an ability to write more precisely

  instance AMonad H where 

  instance FAMonad K where 


~~~BIG Example~~~~

Let try to divide "class (Eq a)=>Ord a" to both:

ORIGINAL ONE:
  class  (Eq a) => Ord a  where
    compare              :: a -> a -> Ordering
    ...

    compare x y = if x == y then EQ
                  else if x <= y then LT
                  else GT

Proposed one (it is just an example, not a "real" proposal):

class  Ord' a  where
    ...........
    compare x y = if x < y then LT
                  else if x > y then GT
                  else EQ             -- without Eq it is a last choice


newclass  (Eq a) => Ord at Ord' a  where
    compare x y = if x == y then EQ
                  else if x <= y then LT
                  else GT

So now we have both Ord' a for nonEQ data and for Eq data.
And this has a backward compatibility! 



--
View this message in context: http://haskell.1045720.n5.nabble.com/Proposal-RankedInstances-tp5737152.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list