[GHC] #8370: Ranked Instances

GHC ghc-devs at haskell.org
Fri Sep 27 20:24:50 CEST 2013


#8370: Ranked Instances
------------------------------------+-------------------------------------
       Reporter:  wvv               |             Owner:
           Type:  feature request   |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.6.3
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 This is a first part of 3 depended extensions:
 Ranked Instances => Inherit Instances => Newclasses

 This is very easy to implement. And it gives big advantages. And further
 developing.
 I suggest to add "rank" to instance.

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

 With rankings compiler
 * set N=0
 * took all N-ranked instances and
 * => try to find only one match instance.
 * -> If it found only 1 - this is RESULT: needed instance,
 * -> If it found many instances - throw an error
 * -> If compiler found NO instances, compiler set N=N+1 and repeat
 * If N=MaxRank and still no matches compiler throw an error

 We use `RankedInstances` '''before''' `OverlappingInstances` (which must
 include `RankedInstances`), and in many cases instead of.


 == Proposed grammar ==

 We add "rank N" between "instance" word and ".", where N is a number

 {{{
   {-# LANGUAGE RankedInstances #-}

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


 == Default Rank ==

 If instance has no rank, this means it has 0 rank

 {{{
   instance         C a => D a where ...
   ~
   instance rank 0. C a => D a where ...
 }}}

 This is a backward compatibility.

 '''Examples'''

 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!


 == Backward Compatibility ==

 Without -XRankedInstances all instances with hight rank n, where n >0 -
 are not exported


 More information (about all 3 extensions) is here
 http://haskell.1045720.n5.nabble.com/Proposal-RankedInstances-
 tt5737152.html

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



More information about the ghc-tickets mailing list