
#13253: Exponential compilation time with RWST & ReaderT stack with `-02` -------------------------------------+------------------------------------- Reporter: phadej | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): I might be pointing out the obvious, but given Simon's example {{{ module Expfoo (f, foo, bar) where f :: Int -> Bool -> Bool {-# INLINE f #-} f y x = case x of { True -> y>0 ; False -> y<0 } foo :: Int -> Bool -> Bool foo y x = f (y+1) $ f (y+2) $ f (y+3) $ f (y+4) $ f (y+5) $ f (y+6) $ f (y+7) $ f (y+8) $ f (y+9) $ f y x bar :: Bool bar = foo 10 True }}} The -ddump-simpl -ddump-simpl-stats say {{{ 2157 PostInlineUnconditionally 2060 x_a28M 2129 KnownBranch 2060 wild_a28K 1024 FillInCaseDefault 512 wild_X1l 256 wild_X1n 128 wild_X1p 64 wild_X1r 32 wild_X1t 16 wild_X1v 8 wild_X1x 4 wild_X1z 2 wild_Xc 2 wild_X1y bar = GHC.Types.True }}} I.e. simplifier is able to calculate `bar` value, which is great! But it does exponential job while trying to figure out what's `foo`. However if we only export {{{ module Expfoo (f, bar) where }}} then `bar` is still `True`, but stats looks way better, all Grand total simplifier statistics are under 12, e.g. {{{ 8 CaseOfCase 8 wild_Xb 73 KnownBranch 11 wild1_a28w 10 wild_a28s 9 wild1_a28m 9 wild_a28K 9 wild1_a28O 8 wild_a28i 2 wild_Xb 2 wild_X17 2 wild_X19 2 wild_X1b 2 wild_X1d 2 wild_X1f 2 wild_X1h 2 wild_X1j 1 wild_X1m 1 FillInCaseDefault 1 wild_Xb 12 SimplifierDone 12 }}} I'm quite sure that while fixing the exponential time issue, we should "break" the fact that `bar` is fully simplified to `True`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13253#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler