[Git][ghc/ghc][master] Add a perf test for the generics code pattern from #21839.

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Thu Oct 13 09:58:35 UTC 2022



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
ce293908 by Andreas Klebinger at 2022-10-13T05:58:19-04:00
Add a perf test for the generics code pattern from #21839.

This code showed a strong shift between compile time (got worse) and
run time (got a lot better) recently which is perfectly acceptable.

However it wasn't clear why the compile time regression was happening
initially so I'm adding this test to make it easier to track such changes
in the future.

- - - - -


6 changed files:

- + testsuite/tests/perf/compiler/T21839c.hs
- + testsuite/tests/perf/compiler/T21839c.stdout
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/perf/should_run/T21839r.hs
- + testsuite/tests/perf/should_run/T21839r.stdout
- testsuite/tests/perf/should_run/all.T


Changes:

=====================================
testsuite/tests/perf/compiler/T21839c.hs
=====================================
@@ -0,0 +1,46 @@
+-- For in depth details see the ticket #21839. The short version:
+
+-- We noticed that GHC got slower compiling Cabal the libary.
+-- Eventually I narrowed it down to the pattern below of deriving Generics
+-- for a Enum, and then deriving a Binary instance for that Enum via Generics.
+-- A pattern very frequently used in Cabal.
+-- However this turned out to be a classic compile vs runtime tradeoff.
+-- In benchmarks I found the resulting code for the Binary instance was running
+-- more than twice as fast!
+-- So we decided to merely document this change and add a test representing this behaviour
+-- rather than trying to coax ghc back into its old behaviour.
+
+{-# LANGUAGE DeriveGeneric #-}
+
+{-# OPTIONS_GHC #-}
+module Main
+  ( main
+  ) where
+
+import GHC.Generics
+import Data.Typeable
+import Data.Binary
+import qualified Data.ByteString.Lazy as BL
+import qualified Data.ByteString as BS
+
+data PathTemplateVariable =
+
+       Var0
+     | Var1
+     | Var2
+     | Var3
+     | Var4
+     | Var5
+     | Var6
+     | Var7
+     | Var8
+     | Var9
+  deriving (Generic,Enum)
+
+instance Binary PathTemplateVariable
+
+main :: IO ()
+main = do
+  let lists = replicate 10000 Var0
+      lbs = encode lists
+  print $ BS.length $ BS.toStrict lbs


=====================================
testsuite/tests/perf/compiler/T21839c.stdout
=====================================
@@ -0,0 +1 @@
+10008


=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -643,3 +643,10 @@ test ('T20261',
       [collect_compiler_stats('all')],
       compile,
       [''])
+
+# Track perf of generics based binary instances
+test('T21839c',
+    [   collect_compiler_stats('all', 1),
+        only_ways(['normal'])],
+    compile,
+    ['-O'])
\ No newline at end of file


=====================================
testsuite/tests/perf/should_run/T21839r.hs
=====================================
@@ -0,0 +1,46 @@
+-- For in depth details see the ticket #21839. The short version:
+
+-- We noticed that GHC got slower compiling Cabal the libary.
+-- Eventually I narrowed it down to the pattern below of deriving Generics
+-- for a Enum, and then deriving a Binary instance for that Enum via Generics.
+-- A pattern very frequently used in Cabal.
+-- However this turned out to be a classic compile vs runtime tradeoff.
+-- In benchmarks I found the resulting code for the Binary instance was running
+-- more than twice as fast!
+-- So we decided to merely document this change and add a test representing this behaviour
+-- rather than trying to coax ghc back into its old behaviour.
+
+{-# LANGUAGE DeriveGeneric #-}
+
+{-# OPTIONS_GHC #-}
+module Main
+  ( main
+  ) where
+
+import GHC.Generics
+import Data.Typeable
+import Data.Binary
+import qualified Data.ByteString.Lazy as BL
+import qualified Data.ByteString as BS
+
+data PathTemplateVariable =
+
+       Var0
+     | Var1
+     | Var2
+     | Var3
+     | Var4
+     | Var5
+     | Var6
+     | Var7
+     | Var8
+     | Var9
+  deriving (Generic,Enum)
+
+instance Binary PathTemplateVariable
+
+main :: IO ()
+main = do
+  let lists = replicate 10000 Var0
+      lbs = encode lists
+  print $ BS.length $ BS.toStrict lbs


=====================================
testsuite/tests/perf/should_run/T21839r.stdout
=====================================
@@ -0,0 +1 @@
+10008


=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -395,3 +395,11 @@ test('T19347',
     compile_and_run,
     ['-O'])
 
+# Track perf of generics based binary instances
+test('T21839r',
+    [   collect_stats('bytes allocated', 10),
+        collect_runtime_residency(10),
+        collect_compiler_stats('bytes allocated', 1),
+        only_ways(['normal'])],
+    compile_and_run,
+    ['-O'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce2939085e5b59513748ff73bc66161c09d69468

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce2939085e5b59513748ff73bc66161c09d69468
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221013/9dc7a7e7/attachment-0001.html>


More information about the ghc-commits mailing list