[commit: ghc] master: Optimise the Typeable instance for type app a bit, and add a perf test (00fc4ba)

git at git.haskell.org git at git.haskell.org
Tue Jun 17 11:42:34 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/00fc4ba2363b466d1178ae6bcaec628c9cde4758/ghc

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

commit 00fc4ba2363b466d1178ae6bcaec628c9cde4758
Author: Simon Marlow <marlowsd at gmail.com>
Date:   Tue Jun 17 11:47:40 2014 +0100

    Optimise the Typeable instance for type app a bit, and add a perf test
    
    Test Plan: validate
    
    Reviewers: simonpj, austin
    
    Subscribers: simonmar, relrod
    
    Differential Revision: https://phabricator.haskell.org/D20


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

00fc4ba2363b466d1178ae6bcaec628c9cde4758
 libraries/base/Data/Typeable/Internal.hs                | 17 ++++++++++++++---
 .../tests/perf/should_run/T9203.hs                      |  3 ---
 .../tests/perf/should_run/T9203.stdout                  |  0
 testsuite/tests/perf/should_run/all.T                   |  8 ++++++++
 4 files changed, 22 insertions(+), 6 deletions(-)

diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 5b1cde4..a09d4ad 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE Unsafe             #-}
+{-# LANGUAGE BangPatterns #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -263,9 +264,19 @@ type Typeable7 (a :: * -> * -> * -> * -> * -> * -> * -> *) = Typeable a
 
 -- | Kind-polymorphic Typeable instance for type application
 instance (Typeable s, Typeable a) => Typeable (s a) where
-  typeRep# = \_ -> rep
-    where rep = typeRep# (proxy# :: Proxy# s)
-                   `mkAppTy` typeRep# (proxy# :: Proxy# a)
+  typeRep# = \_ -> rep                  -- Note [Memoising typeOf]
+    where !ty1 = typeRep# (proxy# :: Proxy# s)
+          !ty2 = typeRep# (proxy# :: Proxy# a)
+          !rep = ty1 `mkAppTy` ty2
+
+{- Note [Memoising typeOf]
+~~~~~~~~~~~~~~~~~~~~~~~~~~
+See #3245, #9203
+
+IMPORTANT: we don't want to recalculate the TypeRep once per call with
+the proxy argument.  This is what went wrong in #3245 and #9203. So we
+help GHC by manually keeping the 'rep' *outside* the lambda.
+-}
 
 ----------------- Showing TypeReps --------------------
 
diff --git a/libraries/base/tests/dynamic003.hs b/testsuite/tests/perf/should_run/T9203.hs
similarity index 69%
copy from libraries/base/tests/dynamic003.hs
copy to testsuite/tests/perf/should_run/T9203.hs
index fae8bdb..500fd8c 100644
--- a/libraries/base/tests/dynamic003.hs
+++ b/testsuite/tests/perf/should_run/T9203.hs
@@ -1,8 +1,5 @@
 module Main where
 
--- Test generation of large TypeReps
--- (can be used as a benchmark)
-
 import Data.Typeable
 
 f :: Typeable a => Int -> a -> TypeRep
diff --git a/libraries/base/tests/dynamic003.stdout b/testsuite/tests/perf/should_run/T9203.stdout
similarity index 100%
copy from libraries/base/tests/dynamic003.stdout
copy to testsuite/tests/perf/should_run/T9203.stdout
diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T
index 8030251..94fd2a3 100644
--- a/testsuite/tests/perf/should_run/all.T
+++ b/testsuite/tests/perf/should_run/all.T
@@ -366,3 +366,11 @@ test('InlineCloneArrayAlloc',
       only_ways(['normal'])],
      compile_and_run,
      ['-O2'])
+
+test('T9203',
+     [stats_num_field('bytes allocated',
+                      [ (wordsize(32), 50000000, 5)
+                      , (wordsize(64), 95747304, 5) ]),
+      only_ways(['normal'])],
+     compile_and_run,
+     ['-O2'])



More information about the ghc-commits mailing list