
#9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: dfeuer Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293, | Differential Rev(s): #13059, #10818 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Here's a truly bare-bones, Haskell 98 reproduction: {{{#!hs module Duh where class Duh a where duh :: Integer -> a noDuh :: a -> Integer class GenDuh a where gduh :: Integer -> a gnoDuh :: a -> Integer instance GenDuh () where gduh = const () gnoDuh = const 1 instance GenDuh a => GenDuh (Maybe a) where gduh 0 = Nothing gduh n = Just (gduh (n - 1)) gnoDuh Nothing = 0 gnoDuh (Just x) = 1 + gnoDuh x data T = T (Maybe (Maybe ())) instance Duh T where duh i = T (gduh i) noDuh (T m) = gnoDuh m }}} GHC 8.2.1rc2 with `-O2 -ddump-ds` produces {{{ -- RHS size: {terms: 13, types: 18, coercions: 0, joins: 0/2} $cnoDuh_aRo :: T -> Integer [LclId] $cnoDuh_aRo = let { $dGenDuh_a2nn :: GenDuh (Maybe ()) [LclId] $dGenDuh_a2nn = Duh.$fGenDuhMaybe @ () Duh.$fGenDuh() } in let { $dGenDuh_aRs :: GenDuh (Maybe (Maybe ())) [LclId] $dGenDuh_aRs = Duh.$fGenDuhMaybe @ (Maybe ()) $dGenDuh_a2nn } in \ (ds_d2ow :: T) -> case ds_d2ow of { T m_azN -> gnoDuh @ (Maybe (Maybe ())) $dGenDuh_aRs m_azN } -- RHS size: {terms: 11, types: 14, coercions: 0, joins: 0/2} $cduh_aRi :: Integer -> T [LclId] $cduh_aRi = let { $dGenDuh_a2nl :: GenDuh (Maybe ()) [LclId] $dGenDuh_a2nl = Duh.$fGenDuhMaybe @ () Duh.$fGenDuh() } in let { $dGenDuh_aRm :: GenDuh (Maybe (Maybe ())) [LclId] $dGenDuh_aRm = Duh.$fGenDuhMaybe @ (Maybe ()) $dGenDuh_a2nl } in \ (i_azM :: Integer) -> Duh.T (gduh @ (Maybe (Maybe ())) $dGenDuh_aRm i_azM) }}} We solve the `GenDuh (Maybe (Maybe ()))` constraint twice, and build its dictionary twice. I'll attach `-ddump-tc-trace`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9630#comment:56 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler