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

GHC ghc-devs at haskell.org
Tue Jan 3 02:37:26 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:
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:                    |
-------------------------------------+-------------------------------------
Description changed by ezyang:

@@ -1,2 +1,2 @@
- This file never finishes compiling on GHC 8.0.1, and GHC 8.0.2 (dated
- 20161213):
+ This file never finishes compiling with optimization (`-O`) on GHC 8.0.1,
+ and GHC 8.0.2 (dated 20161213):

New description:

 This file never finishes compiling with optimization (`-O`) on GHC 8.0.1,
 and GHC 8.0.2 (dated 20161213):

 {{{
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE DeriveFunctor #-}
 {-# LANGUAGE DeriveFoldable #-}

 module Bug where
 import Data.Typeable
 import GHC.Generics
 import Data.Data

 data Condition v = Condition
     deriving (Functor, Foldable)

 data CondTree v c a = CondNode
     { condTreeData        :: a
     , condTreeConstraints :: c
     , condTreeComponents  :: [CondBranch v c a]
     }
     deriving (Functor, Foldable)

 data CondBranch v c a = CondBranch
     { condBranchCondition :: Condition v
     , condBranchIfTrue    :: CondTree v c a
     , condBranchIfFalse   :: Maybe (CondTree v c a)
     }
     deriving (Functor, Foldable)
 }}}

 The problem seems to be fixed in HEAD but I haven't looked for the commit
 that fixed it.

--

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


More information about the ghc-tickets mailing list