[GHC] #8370: Ranked Instances

GHC ghc-devs at haskell.org
Sat Sep 28 21:05:20 CEST 2013


#8370: Ranked Instances
-------------------------------------+------------------------------------
        Reporter:  wvv               |            Owner:
            Type:  feature request   |           Status:  closed
        Priority:  normal            |        Milestone:
       Component:  Compiler          |          Version:  7.6.3
      Resolution:  invalid           |         Keywords:
Operating System:  Unknown/Multiple  |     Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown      |       Difficulty:  Unknown
       Test Case:                    |       Blocked By:
        Blocking:                    |  Related Tickets:
-------------------------------------+------------------------------------

Comment (by wvv):

 I'm really deeply appreciated !

 And I'm really sorry if my examples are not understandable and my
 explanation isn't clearly enough ((

 Here is a background: the main power of Haskell is type-classes and their
 implementation: instances. So, Haskell is interested to have as much
 instances as it can for any cases.

 Unfortunately we can't have a lot of instances - they became to overlap
 each other. In many cases Overlapping Instances doesn't solve our
 problems. GHC add "default" instances. But it is a partially solved
 problem.

 For now we are capable to write next:

 {{{
   instance Monad m => Functor m where
     fmap = liftM

   instance Applicative m => Functor m where
     fmap f x = pure f <*> x
 }}}

 But we cannot add them of overlapping reason. Both of them not only
 overlap with any concrete instance but each other.
 "Defaulting" and overlapping won't help us to solve this.
 All (except hidden with "defaulting") superclass' instances like:
 {{{
 instance Child a => Parent a where ..
 }}}
 are forbidden

 == (1) ==
  Ranked Instances allow us to create and use all `Child a => Parent a`
 superclass' instances

 {{{
   class Applicative f where ... --without "Functor f=>", it is a
 misfeature

   instance rank 15. Monad m => Functor m where
     fmap = liftM

   instance rank 16. Applicative m => Functor m where
     fmap f x = pure f <*> x
 }}}
  Compiler try use all 0-ranked instances, then all 1-ranked, then ...,
 then all 14-ranked, then all 15-ranked.

  If instances overlap in any rank-layer, it is an error.
  Our 2 instances are in different layers, so we have no overlapping.

  All user's instances by default are 0-ranked. So if user create data, add
 2 instances: Monad and Applicative,
 {{{
  data D a ...

  instance Monad D where ...

  class Applicative f where ... --without "Functor f=>"
  instance Applicative D where ...

 }}}
  and not Functor, but try to use `fmap`
 {{{
    foo = (+) `fmap` D 1
 }}}
  compiler use (Monad m => Functor m) instance, reason - lower rank, than
 (Applicative m => Functor m). If user define his own instance Functor
 data,
 {{{
    instance {- ranked 0. -} Functor D where ..
 }}}
  it will be 0-ranked instance, so compiler use his instance, not
 superclass' instance (with much higher rank).

  ''A lot of Child2Parent superclass' instances are the unique feature of
 this extension! ''

 == (2) ==
  Ranked Instances allow us to get rid of default instances, but save all
 capabilities of it. Even more - with Ranked Instances is allowed to use
 several default-like instances (outside of class)

 {{{
    class ToJSON a where
      toJSON   :: a -> Value
      default instance (Generic a, GToJSON (Rep a)) => ToJSON a where
         toJSON = genericToJSON defaultOptions
 }}}
  is the same as
 {{{

    class ToJSON a where
      toJSON   :: a -> Value

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

    instance rank 11. (Data a) => ToJSON a where ...

 }}}
  Here we have 2 default-like instances! If we wish to add third, I dunno,
 "Typeable a=> ToJson a" we still could add it (with higher rank).

  ''We'll have with Ranked Instances much more, then with default
 instances! ''

 == (3) ==
  Ranked Instances are powerful enough to use them instead of both
 Overlapping Instances and Incoherent Instances.

 {{{
    instance rank 3. C a    Int  Bool  where ...
    instance rank 2. C Int  Int  a     where ...
    instance rank 1. C a    Bool a     where ...
    instance rank 0. C Bool a    Bool  where ...
 }}}
  Neither Overlapping Instances, nor Incoherent Instances can't help us in
 this situation.

  With Ranked Instances, Compiler try to

   1)        0-rank: look if first and third args are Bool

   2) if no, 1-rank: look if second arg is Bool

   3) if no, 2-rank: look if first and second args are Int

   4) if no, 3-rank: look if second argument is Int and third is Bool

   5) if no, throw an error

  ''We'll have with Ranked Instances much more, then Overlapping Instances
 and Incoherent Instances together! ''

 == (S) ==

 If we summarize, Ranked Instances is a very powerful extension!

 It is easy to implement, easy to use and easy to read the code.

 It is compatible with all old code and other extensions.

 It is a step forward, not aside.

 It allows to write more generic code.

 It helps to get rid of boilerplate.

 I suppose, for now my proposal looks much more clearly.
 If it is something unclear, I give more explanation.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8370#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list