[commit: ghc] ghc-8.0: ghc-prim: Delay inlining of {gt, ge, lt, le}Int to phase 1 (c816395)

git at git.haskell.org git at git.haskell.org
Wed Mar 30 19:49:38 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/c8163959e03d9c5777d3b02be38f3591d3d169a2/ghc

>---------------------------------------------------------------

commit c8163959e03d9c5777d3b02be38f3591d3d169a2
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Wed Mar 30 10:09:36 2016 +0200

    ghc-prim: Delay inlining of {gt,ge,lt,le}Int to phase 1
    
    Otherwise rewrite rules may not get an opporunity to fire.
    
    (cherry picked from commit d1179c4bff6d05cc9e86eee3e2d2cee707983c90)


>---------------------------------------------------------------

c8163959e03d9c5777d3b02be38f3591d3d169a2
 libraries/ghc-prim/GHC/Classes.hs          | 18 ++++++++++++------
 testsuite/tests/perf/compiler/T4007.stdout |  4 ++--
 testsuite/tests/perf/haddock/all.T         |  5 +++--
 3 files changed, 17 insertions(+), 10 deletions(-)

diff --git a/libraries/ghc-prim/GHC/Classes.hs b/libraries/ghc-prim/GHC/Classes.hs
index a9d5111..65fdfcc 100644
--- a/libraries/ghc-prim/GHC/Classes.hs
+++ b/libraries/ghc-prim/GHC/Classes.hs
@@ -90,8 +90,8 @@ the @(==)@ class operation rule may rewrite the predicate before our @break@
 rule has a chance to fire.
 
 For this reason, most of the primitive types in @base@ have 'Eq' instances
-defined in terms of helper functions with delayed inlinings. For instance,
- at Word8@\'s @Eq@ instance looks like,
+defined in terms of helper functions with inlinings delayed to phase 1. For
+instance, @Word8@\'s @Eq@ instance looks like,
 
 > instance Eq Word8 where
 >     (==) = eqWord8
@@ -176,6 +176,7 @@ instance Eq Word where
     (==) = eqWord
     (/=) = neWord
 
+-- See GHC.Classes#matching_overloaded_methods_in_rules
 {-# INLINE [1] eqWord #-}
 {-# INLINE [1] neWord #-}
 eqWord, neWord :: Word -> Word -> Bool
@@ -187,6 +188,7 @@ instance Eq Char where
     (==) = eqChar
     (/=) = neChar
 
+-- See GHC.Classes#matching_overloaded_methods_in_rules
 {-# INLINE [1] eqChar #-}
 {-# INLINE [1] neChar #-}
 eqChar, neChar :: Char -> Char -> Bool
@@ -196,6 +198,7 @@ eqChar, neChar :: Char -> Char -> Bool
 instance Eq Float where
     (==) = eqFloat
 
+-- See GHC.Classes#matching_overloaded_methods_in_rules
 {-# INLINE [1] eqFloat #-}
 eqFloat :: Float -> Float -> Bool
 (F# x) `eqFloat` (F# y) = isTrue# (x `eqFloat#` y)
@@ -203,6 +206,7 @@ eqFloat :: Float -> Float -> Bool
 instance Eq Double where
     (==) = eqDouble
 
+-- See GHC.Classes#matching_overloaded_methods_in_rules
 {-# INLINE [1] eqDouble #-}
 eqDouble :: Double -> Double -> Bool
 (D# x) `eqDouble` (D# y) = isTrue# (x ==## y)
@@ -211,6 +215,7 @@ instance Eq Int where
     (==) = eqInt
     (/=) = neInt
 
+-- See GHC.Classes#matching_overloaded_methods_in_rules
 {-# INLINE [1] eqInt #-}
 {-# INLINE [1] neInt #-}
 eqInt, neInt :: Int -> Int -> Bool
@@ -363,10 +368,11 @@ instance Ord Int where
     (>=)    = geInt
     (>)     = gtInt
 
-{-# INLINE gtInt #-}
-{-# INLINE geInt #-}
-{-# INLINE ltInt #-}
-{-# INLINE leInt #-}
+-- See GHC.Classes#matching_overloaded_methods_in_rules
+{-# INLINE [1] gtInt #-}
+{-# INLINE [1] geInt #-}
+{-# INLINE [1] ltInt #-}
+{-# INLINE [1] leInt #-}
 gtInt, geInt, ltInt, leInt :: Int -> Int -> Bool
 (I# x) `gtInt` (I# y) = isTrue# (x >#  y)
 (I# x) `geInt` (I# y) = isTrue# (x >=# y)
diff --git a/testsuite/tests/perf/compiler/T4007.stdout b/testsuite/tests/perf/compiler/T4007.stdout
index c924781..e7ccd42 100644
--- a/testsuite/tests/perf/compiler/T4007.stdout
+++ b/testsuite/tests/perf/compiler/T4007.stdout
@@ -7,8 +7,8 @@ Rule fired: Class op return
 Rule fired: Class op foldr
 Rule fired: Class op >>
 Rule fired: Class op return
-Rule fired: <#
-Rule fired: tagToEnum#
 Rule fired: Class op foldr
 Rule fired: fold/build
+Rule fired: <#
+Rule fired: tagToEnum#
 Rule fired: unpack-list
diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T
index 4818c20..c33efcf 100644
--- a/testsuite/tests/perf/haddock/all.T
+++ b/testsuite/tests/perf/haddock/all.T
@@ -51,7 +51,7 @@ test('haddock.base',
 test('haddock.Cabal',
      [unless(in_tree_compiler(), skip), req_haddock
      ,stats_num_field('bytes allocated',
-          [(wordsize(64), 11123698216, 5)
+          [(wordsize(64), 10941742184, 5)
             # 2012-08-14: 3255435248 (amd64/Linux)
             # 2012-08-29: 3324606664 (amd64/Linux, new codegen)
             # 2012-10-08: 3373401360 (amd64/Linux)
@@ -75,7 +75,8 @@ test('haddock.Cabal',
             # 2015-12-11: 8114833312 (amd64/Linux) - TypeInType (See #11196)
             # 2015-12-17: 9982130512 (amd64/Linux) - Update Haddock to master
             # 2015-12-22: 10519532424 (amd64/Linux) - Lots of new Semigroup instances in Cabal
-            # 2015-03-08: 11123698216 (amd64/Linux) - Cabal update
+            # 2016-03-29: 11517963232 (amd64/Linux) - not yet investigated
+            # 2016-03-30: 10941742184 (amd64/Linux) - defer inlining of Int* Ord methods
 
           ,(platform('i386-unknown-mingw32'), 3293415576, 5)
             # 2012-10-30:                     1733638168 (x86/Windows)



More information about the ghc-commits mailing list