Skip to content
Snippets Groups Projects
Commit ce293908 authored by Andreas Klebinger's avatar Andreas Klebinger Committed by Marge Bot
Browse files

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.
parent 5172789a
No related merge requests found
Pipeline #57791 canceled
-- 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
10008
......@@ -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
-- 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
10008
......@@ -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'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment