[commit: ghc] master: Compiler performance benchmark for #9675 (05f962d)

git at git.haskell.org git at git.haskell.org
Mon Oct 13 10:24:51 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/05f962df2ba028fd304fdada9e68e7199822cbf0/ghc

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

commit 05f962df2ba028fd304fdada9e68e7199822cbf0
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Mon Oct 13 11:27:17 2014 +0200

    Compiler performance benchmark for #9675
    
    so that whoever improves the situation can feel good about it.


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

05f962df2ba028fd304fdada9e68e7199822cbf0
 testsuite/tests/perf/compiler/T9675.hs | 103 +++++++++++++++++++++++++++++++++
 testsuite/tests/perf/compiler/all.T    |  18 ++++++
 2 files changed, 121 insertions(+)

diff --git a/testsuite/tests/perf/compiler/T9675.hs b/testsuite/tests/perf/compiler/T9675.hs
new file mode 100644
index 0000000..6ea64de
--- /dev/null
+++ b/testsuite/tests/perf/compiler/T9675.hs
@@ -0,0 +1,103 @@
+module T6975 where
+data Foo = Foo
+  { field1 :: Int -> Int
+  , field2 :: Int -> Int
+  , field3 :: Int -> Int
+  , field4 :: Int -> Int
+  , field5 :: Int -> Int
+  , field6 :: Int -> Int
+  , field7 :: Int -> Int
+  , field8 :: Int -> Int
+  , field9 :: Int -> Int
+  , field10 :: Int -> Int
+  , field11 :: Int -> Int
+  , field12 :: Int -> Int
+  , field13 :: Int -> Int
+  , field14 :: Int -> Int
+  , field15 :: Int -> Int
+  , field16 :: Int -> Int
+  , field17 :: Int -> Int
+  , field18 :: Int -> Int
+  , field19 :: Int -> Int
+  , field20 :: Int -> Int
+  , field21 :: Int -> Int
+  , field22 :: Int -> Int
+  , field23 :: Int -> Int
+  , field24 :: Int -> Int
+  , field25 :: Int -> Int
+  , field26 :: Int -> Int
+  , field27 :: Int -> Int
+  , field28 :: Int -> Int
+  , field29 :: Int -> Int
+  , field30 :: Int -> Int
+  , field31 :: Int -> Int
+  , field32 :: Int -> Int
+  , field33 :: Int -> Int
+  , field34 :: Int -> Int
+  , field35 :: Int -> Int
+  , field36 :: Int -> Int
+  , field37 :: Int -> Int
+  , field38 :: Int -> Int
+  , field39 :: Int -> Int
+  , field40 :: Int -> Int
+  , field41 :: Int -> Int
+  , field42 :: Int -> Int
+  , field43 :: Int -> Int
+  , field44 :: Int -> Int
+  , field45 :: Int -> Int
+  , field46 :: Int -> Int
+  , field47 :: Int -> Int
+  , field48 :: Int -> Int
+  , field49 :: Int -> Int
+  , field50 :: Int -> Int
+  , field51 :: Int -> Int
+  , field52 :: Int -> Int
+  , field53 :: Int -> Int
+  , field54 :: Int -> Int
+  , field55 :: Int -> Int
+  , field56 :: Int -> Int
+  , field57 :: Int -> Int
+  , field58 :: Int -> Int
+  , field59 :: Int -> Int
+  , field60 :: Int -> Int
+  , field61 :: Int -> Int
+  , field62 :: Int -> Int
+  , field63 :: Int -> Int
+  , field64 :: Int -> Int
+  , field65 :: Int -> Int
+  , field66 :: Int -> Int
+  , field67 :: Int -> Int
+  , field68 :: Int -> Int
+  , field69 :: Int -> Int
+  , field70 :: Int -> Int
+  , field71 :: Int -> Int
+  , field72 :: Int -> Int
+  , field73 :: Int -> Int
+  , field74 :: Int -> Int
+  , field75 :: Int -> Int
+  , field76 :: Int -> Int
+  , field77 :: Int -> Int
+  , field78 :: Int -> Int
+  , field79 :: Int -> Int
+  , field80 :: Int -> Int
+  , field81 :: Int -> Int
+  , field82 :: Int -> Int
+  , field83 :: Int -> Int
+  , field84 :: Int -> Int
+  , field85 :: Int -> Int
+  , field86 :: Int -> Int
+  , field87 :: Int -> Int
+  , field88 :: Int -> Int
+  , field89 :: Int -> Int
+  , field90 :: Int -> Int
+  , field91 :: Int -> Int
+  , field92 :: Int -> Int
+  , field93 :: Int -> Int
+  , field94 :: Int -> Int
+  , field95 :: Int -> Int
+  , field96 :: Int -> Int
+  , field97 :: Int -> Int
+  , field98 :: Int -> Int
+  , field99 :: Int -> Int
+  , field100 :: Int -> Int
+ }
diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T
index 1afcf88..1de224e 100644
--- a/testsuite/tests/perf/compiler/all.T
+++ b/testsuite/tests/perf/compiler/all.T
@@ -492,3 +492,21 @@ test('T9020',
            # 2014-09-10:  785871680 post-AMP-cleanup
       ],
       compile,[''])
+
+test('T9675',
+     [ only_ways(['optasm']),
+       compiler_stats_num_field('max_bytes_used',
+          [(wordsize(64), 25822728, 15),
+          # 2014-10-13    25822728
+          ]),
+       compiler_stats_num_field('peak_megabytes_allocated',
+          [(wordsize(64), 62, 1),
+          # 2014-10-13    62
+          ]),
+       compiler_stats_num_field('bytes allocated',
+          [(wordsize(64), 601441240, 1)
+          # 2014-10-13    601441240
+          ]),
+      ],
+     compile,
+     [''])



More information about the ghc-commits mailing list