[GHC] #13056: Deriving Foldable causes GHC to take a long time (GHC 8.0 ONLY)

GHC ghc-devs at haskell.org
Tue Jan 3 16:32:00 UTC 2017


#13056: Deriving Foldable causes GHC to take a long time (GHC 8.0 ONLY)
-------------------------------------+-------------------------------------
        Reporter:  ezyang            |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.2-rc2
      Resolution:                    |             Keywords:  deriving-perf
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 RyanGlScott):

 * keywords:   => deriving-perf


Comment:

 Here's a stripped-down version that doesn't use any GHC extensions:

 {{{#!hs
 module Bug where

 newtype CondTree a = CondNode
     { condTreeComponents :: [CondBranch a]
     }

 data CondBranch a = CondBranch
     { condBranchIfTrue  :: CondTree a
     , condBranchIfFalse :: CondTree a
     }

 instance Foldable CondBranch where
   foldr f_a3sF z_a3sG (CondBranch a1_a3sH a2_a3sI)
     = (\ b1_a3sJ b2_a3sK -> foldr f_a3sF b2_a3sK b1_a3sJ)
         a1_a3sH
         ((\ b3_a3sL b4_a3sM -> foldr f_a3sF b4_a3sM b3_a3sL)
            a2_a3sI z_a3sG)
   foldMap f_a3sN (CondBranch a1_a3sO a2_a3sP)
     = mappend
         (foldMap f_a3sN a1_a3sO)
         (foldMap f_a3sN a2_a3sP)

 instance Foldable CondTree where
   foldr f_a3sQ z_a3sR (CondNode a1_a3sS)
     = (\ b3_a3sT b4_a3sU
          -> foldr
               (\ b1_a3sV b2_a3sW -> foldr f_a3sQ b2_a3sW b1_a3sV)
               b4_a3sU
               b3_a3sT)
         a1_a3sS z_a3sR
   foldMap f_a3sX (CondNode a1_a3sY)
     = foldMap (foldMap f_a3sX) a1_a3sY
 }}}

 This shows that the program doesn't loop forever, but rather it just takes
 a long time to compile:

 {{{
 $ time /opt/ghc/8.0.1/bin/ghc -O1 -fforce-recomp Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 real    0m3.331s
 user    0m3.280s
 sys     0m0.044s
 }}}

 Adding more polymorphic recursion increases compilation time
 exponentially. For example, this program (with a modified definition and
 `Foldable` instance for `CondBranch`):

 {{{#!hs
 module Bug where

 newtype CondTree a = CondNode
     { condTreeComponents :: [CondBranch a]
     }

 data CondBranch a = CondBranch
     { condBranchIfTrue  :: CondTree a
     , condBranchIfFalse :: Maybe (CondTree a)
     }

 instance Foldable CondBranch where
   foldr f_a3sL z_a3sM (CondBranch a1_a3sN a2_a3sO)
     = (\ b1_a3sP b2_a3sQ -> foldr f_a3sL b2_a3sQ b1_a3sP)
         a1_a3sN
         ((\ b5_a3sR b6_a3sS
             -> foldr
                  (\ b3_a3sT b4_a3sU -> foldr f_a3sL b4_a3sU b3_a3sT)
                  b6_a3sS
                  b5_a3sR)
            a2_a3sO z_a3sM)
   foldMap f_a3sV (CondBranch a1_a3sW a2_a3sX)
     = mappend
         (foldMap f_a3sV a1_a3sW)
         (foldMap (foldMap f_a3sV) a2_a3sX)

 instance Foldable CondTree where
   foldr f_a3sY z_a3sZ (CondNode a1_a3t0)
     = (\ b3_a3t1 b4_a3t2
          -> foldr
               (\ b1_a3t3 b2_a3t4 -> foldr f_a3sY b2_a3t4 b1_a3t3)
               b4_a3t2
               b3_a3t1)
         a1_a3t0 z_a3sZ
   foldMap f_a3t5 (CondNode a1_a3t6)
     = foldMap (foldMap f_a3t5) a1_a3t6
 }}}

 has twice the compilation time.

 {{{
 $ time /opt/ghc/8.0.1/bin/ghc -O1 -fforce-recomp Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

 real    0m6.489s
 user    0m6.396s
 sys     0m0.092s
 }}}

 Now to find the commit responsible for fixing this and backport it to GHC
 8.0.3. I have a hunch that it's the same commit that fixed #12234, but
 it'll be nice to confirm it.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13056#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list