[GHC] #7797: re-enable the defun RULE from a SPECIALISE instance pragma

#7797: re-enable the defun RULE from a SPECIALISE instance pragma -----------------------------+---------------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.2 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- As of commit [https://github.com/ghc/ghc/commit/51d89a55c3 51d89a55c3], `SPECIALISE instance` pragmas do not result in a RULE for the dictionary function. For example, consider this `Eq` instance for `List`. {{{ module M where data List a = Nil | Cons a (List a) instance (Eq a) => Eq (List a) where {-# SPECIALISE instance Eq (List Char) #-} Nil == Nil = True (Cons x xs) == (Cons y ys) = x == y && xs == ys _xs == _ys = False }}} With ghc-7.4.2, we get: {{{ ==================== Tidy Core rules ==================== "SPEC $c/=" [ALWAYS] forall ($dEq :: GHC.Classes.Eq GHC.Types.Char). M.$fEqList_$c/=1 @ GHC.Types.Char $dEq = M.$fEqList_$c/= "SPEC $c==" [ALWAYS] forall ($dEq :: GHC.Classes.Eq GHC.Types.Char). M.$fEqList_$c==1 @ GHC.Types.Char $dEq = M.$fEqList_$c== "SPEC M.$fEqList" [ALWAYS] forall ($dEq :: GHC.Classes.Eq GHC.Types.Char). M.$fEqList @ GHC.Types.Char $dEq = M.$fEqList_$fEqList }}} Note the last rule: it specializes the normal defun `M.$fEqList` when applied at type `Char`. With anything after 7.4.2 -- eg if you download the binary sources for 7.4.2 and make [https://github.com/ghc/ghc/commit/51d89a55c3#L0L779 the change at line 779] from that commit --- you instead get this: {{{ ==================== Tidy Core rules ==================== "SPEC $c/=" [ALWAYS] forall ($dEq :: GHC.Classes.Eq GHC.Types.Char). M.$fEqList_$c/=1 @ GHC.Types.Char $dEq = M.$fEqList_$c/= "SPEC $c==" [ALWAYS] forall ($dEq :: GHC.Classes.Eq GHC.Types.Char). M.$fEqList_$c==1 @ GHC.Types.Char $dEq = M.$fEqList_$c== }}} (Actually, after some patch the /= RULE disappears too, but I don't know which/why.) If the dictionary is used at the relevant type in the same module, the specializer will automatically create the omitted rule. That will not, however, currently happen across module boundaries. In my contrived example, omitting this defun specialization increases runtime by a factor of 2 at -O1. {{{ {-# LANGUAGE ExistentialQuantification #-} module Main where import M data Box = forall a. Eq a => Box a a box = Box (go 10000000) (go 10000000) where go :: Int -> List Char go 0 = Nil go n = Cons 'c' $ go (n - 1) {-# NOINLINE box #-} main = print $ case box of Box l r -> l == r }}} (-O2 squashes the runtime difference; I haven't investigated in detail.) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7797 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7797: re-enable the defun RULE from a SPECIALISE instance pragma -----------------------------+---------------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.2 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Comment(by nfrisby): I'm talked to SPJ about this and the concern is that the defun specialisation may interfere with the specialization of method selections. We think it'll just require some careful thinking and a bit of refactoring of defun inlinings. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7797#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7797: re-enable the defun RULE from a SPECIALISE instance pragma -----------------------------+---------------------------------------------- Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.2 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Changes (by nfrisby): * cc: nfrisby (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7797#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7797: re-enable the defun RULE from a SPECIALISE instance pragma ---------------------------------+------------------------------------------ Reporter: nfrisby | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.2 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Changes (by igloo): * difficulty: => Unknown * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7797#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC