[GHC] #8370: Ranked Instances

GHC ghc-devs at haskell.org
Sun Sep 29 13:04:54 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):

 Wow! Great book! Thank you very much!


 == Contribution ==

 I have Windows without VM. And even compile GHC from 0 (even without any
 contribution)  will be a big challenge ))
 So, maybe this is not an option right now.

 == Easy Implemetation ==

 I'm not familiar with low-Haskell code, but yes, it is easy!

 We can divide changes to support code and significant code.


 == Support code ==

 This is a dev's routine, I a newbie with these techniques.  It is needed
 to

 - add extension name to extension

 - add parsing extension pragma

 - add line "use -XRankedInstances or -XOverlappingInstances" in error
 message if both RankedInstances and OverlappingInstances are off

 - I recommend deny to use both RankedInstances and OverlappingInstances in
 one module

 - add data Ranked-Instances, absolutely similar as data Overlapping-
 Instances

 - add parsing pattern to parser/Parser.y.pp, something like `| "instance"
 "rank" digits "." <rest>` . But forbid to parse without extension

 - extract number

 - and add "rank" field to all data Instance<Smth> and copy-paste this
 field everywhere it is needed.


 == Significant code ==

 Fortunately, almost all code is already written by guys, who added
 Overlapping instances to GHC!

 The reason - Ranked Instances are "user control overlapping".

 http://ghc.haskell.org/trac/ghc/browser/ghc/compiler/types/InstEnv.lhs#L564

 {{{
   lookupInstEnv ... =
             pruned_matches = foldr insert_overlapping [] all_matches
             (safe_matches, safe_fail) = if length pruned_matches == 1
                                 then check_safe (head pruned_matches)
 all_matches
                                 else (pruned_matches, False)
 }}}

 We need to change 2 functions - `insert_overlapping` and `check_safe`.

 ''' insert_overlapping '''

 Let's look to `insert_overlapping` :
 http://ghc.haskell.org/trac/ghc/browser/ghc/compiler/types/InstEnv.lhs#L618

 This function is fully satisfied, exept for `beats` sub-function.
 http://ghc.haskell.org/trac/ghc/browser/ghc/compiler/types/InstEnv.lhs#L641


 {{{
  (instA, _) `beats` (instB, _)
     = overlap_ok &&
       isJust (tcMatchTys (mkVarSet (is_tvs instB)) (is_tys instB) (is_tys
 instA))
                -- A beats B if A is more specific than B,
                -- (ie. if B can be instantiated to match A)
                -- and overlap is permitted
 }}}

 We cahange it to

 {{{
  (instA, _) `beats` (instB, _)
     = (fromRank instA < fromRank instB) ||
    {- We don't need to check if extension is on,
       all non-extension instances have a privilege - the lowest 0 rank -}
     overlap_ok && ...
 }}}

 We add (!) just 1 line of significant code.

 ''' check_safe '''

 This a bit complicated. Devs, who add Overlapping instances add a guard :
 "We restrict code compiled in 'Safe' mode from overriding code compiled in
 any other mode."

 But we wish to allow over-rank instances through the modules.
 The simplest way - to forbid use Overlapped-Instances together with
 Ranked-Instances in one module.
 And add such lines from:
 http://ghc.haskell.org/trac/ghc/browser/ghc/compiler/types/InstEnv.lhs#L609

 {{{
             inSameMod b =
                         let na = getName $ getName inst
                             la = isInternalName na
                             nb = getName $ getName b
                             lb = isInternalName nb
                         in (la && lb) || (nameModule na == nameModule nb)
 }}}
 into (this is not effective code, looks a bit hacky, but it works):
 {{{
             inSameMod b =
                         let na = getName $ getName inst
                             la' = isInternalName na
                             la = isRankedExtension || la' -- allowing Rank
                             nb = getName $ getName b
                             lb' = isInternalName nb
                             lb = isRankedExtension || lb' -- allowing Rank
                         in (la && lb) || (nameModule na == nameModule nb)
 }}}


 == Conclusion ==

 Yes, Ranked Instances is very powerful extension! And yes, it is easy to
 implement!

 Yes, I'm confused, no one even reply at my proposal. I don't even speak
 about serious discussions.

 And yes, I regret, I have no one advocate through developers, who could
 add this extension less than a day in a test branch.

 I've showed, how to add 3 lines of significant code (sure, it is needed
 some routine code for support this extension.)

 I hope, it's become clearer.

 Am I missing something?
 Is it still overly complex in implementation?

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



More information about the ghc-tickets mailing list