[commit: ghc] master: Add performance test for #13056 (5088110)

git at git.haskell.org git at git.haskell.org
Fri Jan 6 14:37:07 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/508811004d1806b28a91c3ff4a5c2247e2ad4655/ghc

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

commit 508811004d1806b28a91c3ff4a5c2247e2ad4655
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Wed Jan 4 13:57:25 2017 -0500

    Add performance test for #13056
    
    This performance regression was fixed by commit
    517d03e41b4f5c144d1ad684539340421be2be2a (#12234). Let's add a performance test
    to ensure that it doesn't break again.


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

508811004d1806b28a91c3ff4a5c2247e2ad4655
 testsuite/tests/perf/compiler/T13056.hs | 26 ++++++++++++++++++++++++++
 testsuite/tests/perf/compiler/all.T     | 11 ++++++++++-
 2 files changed, 36 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/perf/compiler/T13056.hs b/testsuite/tests/perf/compiler/T13056.hs
new file mode 100644
index 0000000..046e1b0
--- /dev/null
+++ b/testsuite/tests/perf/compiler/T13056.hs
@@ -0,0 +1,26 @@
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DeriveFoldable #-}
+
+module Bug where
+import Data.Typeable
+import GHC.Generics
+import Data.Data
+
+data Condition v = Condition
+    deriving (Functor, Foldable)
+
+data CondTree v c a = CondNode
+    { condTreeData        :: a
+    , condTreeConstraints :: c
+    , condTreeComponents  :: [CondBranch v c a]
+    }
+    deriving (Functor, Foldable)
+
+data CondBranch v c a = CondBranch
+    { condBranchCondition :: Condition v
+    , condBranchIfTrue    :: CondTree v c a
+    , condBranchIfFalse   :: Maybe (CondTree v c a)
+    }
+    deriving (Functor, Foldable)
diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index c9ed905..3b5e5bf 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -902,7 +902,6 @@ test('T12234',
      compile,
      [''])
 
-
 test('T13035',
      [ only_ways(['normal']),
        compiler_stats_num_field('bytes allocated',
@@ -912,3 +911,13 @@ test('T13035',
      ],
      compile,
      [''] )
+
+test('T13056',
+     [ only_ways(['optasm']),
+       compiler_stats_num_field('bytes allocated',
+         [(wordsize(64), 520166912, 5),
+         # 2017-01-06    520166912 initial
+         ]),
+     ],
+     compile,
+     ['-O1'])



More information about the ghc-commits mailing list