
#12234: 'deriving Eq' on recursive datatype makes ghc eat a lot of CPU and RAM -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by ezyang: @@ -11,1 +11,0 @@ - {- # OPTIONS_GHC -O1 #-} New description: The example is slimmed down unit test of Annotations-0.2.1 hackage package. If we try to compile Bug.hs with -O0 it compiles quickly. Trying it with -O1 makes GHC-8.0.1 takes a minute to finish. {{{#!hs -- Bug1.hs: {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} module Bug () where import Prelude (Eq) data ExprF rT = ExprF rT rT deriving Eq newtype Expr = Expr (Fix ExprF) deriving Eq newtype Fix fT = In (fT (Fix fT)) deriving instance Eq (f (Fix f)) => Eq (Fix f) }}} {{{ $ time ghc-8.0.1 -c -O0 Bug1.hs -fforce-recomp real 0m0.611s user 0m0.549s sys 0m0.053s $ time ghc-8.0.1 -c -O1 Bug1.hs -fforce-recomp real 1m2.199s user 1m1.676s sys 0m0.465s }}} 7.10.2 for comparison is very quick in both O0/O1: {{{ $ time ghc-7.10.2 -c -O0 Bug1.hs -fforce-recomp real 0m0.220s user 0m0.183s sys 0m0.036s $ time ghc-7.10.2 -c -O1 Bug1.hs -fforce-recomp real 0m0.237s user 0m0.213s sys 0m0.023s }}} The real ExprF datatype uses more constructors and instances: {{{ data ExprF rT = Add rT rT | Sub rT rT | Mul rT rT | Div rT rT | Num Int deriving (Eq, Show) }}} That requires a lot of time and space to finish (Bug2.hs in attach). I've stopped it after 5 minutes (took ~8GB RAM). -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12234#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler