[GHC] #8147: Exponential behavior in instance resolution on fixpoint-of-sum

#8147: Exponential behavior in instance resolution on fixpoint-of-sum -------------------------+------------------------------------------------- Reporter: | Owner: jkoppel | Status: new Type: bug | Milestone: Priority: | Version: 7.6.3 normal | Operating System: Unknown/Multiple Component: | Type of failure: Compile-time performance bug Compiler | Test Case: Keywords: | Blocking: performance, | Architecture: | Unknown/Multiple | Difficulty: | Unknown | Blocked By: | Related Tickets: | -------------------------+------------------------------------------------- Doing instance resolution on a fixpoint-of-sum type takes a very long time. This is possibly the same issue as issue #5642. These are the numbers I see for various n: {{{ 10 : 0.329s 20 : 0.479s 40 : 0.935s 80 : 2.821s 160 : 11.694s 320 : 1m30.39s 640: Ran for over 1 hour without terminating }}} This uses a couple of attached support files. Apologies for not being able to reduce further. {{{ -- Test.hs {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, UndecidableInstances, OverlappingInstances, TypeOperators, DeriveFunctor, TemplateHaskell #-} module Test where import Control.Monad import Lib import TH {- With n=3, produces data X1 e = X1 e deriving (Functor) data X2 e = X2 e deriving (Functor) data X3 e = X3 e deriving (Functor) type X = X1 :+: X2 :+: X3 -} $(let n = 320 in liftM concat $ sequence [liftM concat $ mapM mkDec $ map (('X':).show) [1..n] , makeSumType "X" (map (('X':).show) [1..n])]) data Y0 e = Y0 e deriving ( Functor ) type X' = Y0 :+: X class Lift f g where lift' :: f (Fix g) -> Fix g instance (Lift f g, Lift f' g) => Lift (f :+: f') g where lift' x = case x of L e -> lift' e R e -> lift' e instance (Functor f, f :<: g) => Lift f g where lift' = In . inj cata :: (Functor f) => (f a -> a) -> Fix f -> a cata f = f . fmap (cata f) . out lift :: Fix X -> Fix X' lift = cata lift' }}} Virtually all the time is spent in compiling lift. For example, with n=640, commenting out lift makes it compile in around 2 seconds. Interestingly, when I add the following code, compilation times only increase by 10-20%. In the original code where I encountered this issue, doing so doubles compilation time. {{{ instance Lift Y0 X where lift' = undefined lower :: Fix X' -> Fix X lower = cata lift' }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8147 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8147: Exponential behavior in instance resolution on fixpoint-of-sum -------------------------------------------------+------------------------- Reporter: jkoppel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: | performance, Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------------------+------------------------- Changes (by dfeuer): * Attachment "TH.2.hs" added. Updated TH -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8147 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8147: Exponential behavior in instance resolution on fixpoint-of-sum -------------------------------------------------+------------------------- Reporter: jkoppel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: | performance, Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------------------+------------------------- Changes (by dfeuer): * Attachment "Lib.2.hs" added. Updated Lib -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8147 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8147: Exponential behavior in instance resolution on fixpoint-of-sum -------------------------------------------------+------------------------- Reporter: jkoppel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: | performance, Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------------------+------------------------- Changes (by dfeuer): * Attachment "Test.hs" added. Updated Test -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8147 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8147: Exponential behavior in instance resolution on fixpoint-of-sum -------------------------------------+------------------------------------- Reporter: jkoppel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: performance, 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 dfeuer): The original files no longer work with GHC 8.2.1 as a result of TH changes. I've uploaded new ones that do. Unfortunately, the bug is still with us. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8147#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8147: Exponential behavior in instance resolution on fixpoint-of-sum -------------------------------------+------------------------------------- Reporter: jkoppel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: performance, 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: | -------------------------------------+------------------------------------- Changes (by dfeuer): * Attachment "Test.hs" added. Updated Test -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8147 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8147: Exponential behavior in instance resolution on fixpoint-of-sum -------------------------------------+------------------------------------- Reporter: jkoppel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: performance, 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 dfeuer): Although there's still a bug, it has changed somewhat. We now get a context reduction stack overflow: {{{ Test.hs:43:8: error: • Reduction stack overflow; size = 201 When simplifying the following type: Functor (X201 :+: (X202 :+: (X203 :+: (X204 :+: (X205 ... Use -freduction-depth=0 to disable this check (any upper bound you could choose might fail unpredictably with minor updates to GHC, so disabling the check is recommended if you're sure that type checking should terminate) • In the expression: cata lift' In an equation for ‘lift’: lift = cata lift' | 43 | lift = cata lift' | ^^^^^^^^^^ }}} Removing the reduction depth limit brings my machine to its knees. I can compile the program with `n=120` and a reduction depth limit of 300. One other thing of note: removing the redundant `Functor` constraint on the `Lift f g` instance (which for some reason is not detected as redundant in 8.2.1, though it was in 8.0.2) improves matters considerably, but they're still pretty bad even in that case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8147#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC