[GHC] #13056: Deriving Foldable causes GHC to take a long time (GHC 8.0 ONLY)
GHC
ghc-devs at haskell.org
Wed Jan 4 01:35:22 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: #12234 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* related: => #12234
Comment:
Indeed, commit 517d03e41b4f5c144d1ad684539340421be2be2a (which fixed
#12234) also fixed this issue. I was a bit skeptical that it would, since
I thought #12234 only applies in cases of coercibility-solving for
newtypes, and the original program doesn't appear to use any newtypes. But
then it occurred to me - the original program actually //does// involve
newtypes, but they're hidden in the default definitions of some `Foldable`
class methods:
{{{#!hs
class Foldable t where
-- | The largest element of a non-empty structure.
maximum :: forall a . Ord a => t a -> a
maximum = fromMaybe (errorWithoutStackTrace "maximum: empty
structure") .
getMax . foldMap (Max #. (Just :: a -> Maybe a))
-- | The least element of a non-empty structure.
minimum :: forall a . Ord a => t a -> a
minimum = fromMaybe (errorWithoutStackTrace "minimum: empty
structure") .
getMin . foldMap (Min #. (Just :: a -> Maybe a))
-- | The 'sum' function computes the sum of the numbers of a
structure.
sum :: Num a => t a -> a
sum = getSum #. foldMap Sum
-- | The 'product' function computes the product of the numbers of a
-- structure.
product :: Num a => t a -> a
product = getProduct #. foldMap Product
}}}
And `(#.)` is defined to be:
{{{#!hs
(#.) :: Coercible b c => (b -> c) -> (a -> b) -> (a -> c)
(#.) _f = coerce
}}}
Quite sneaky.
Until we can get 517d03e41b4f5c144d1ad684539340421be2be2a backported to
GHC 8.0.3, a workaround is to manually define these `Foldable` methods for
polymorphically recursive datatypes such that they don't use `coerce`:
{{{#!hs
{-# LANGUAGE CPP #-}
module Bug where
import Data.Maybe (fromMaybe)
newtype CondTree a = CondNode
{ condTreeComponents :: [CondBranch a]
}
data CondBranch a = CondBranch
{ condBranchIfTrue :: CondTree a
, condBranchIfFalse :: Maybe (CondTree a)
}
instance Foldable CondBranch where
foldr f z (CondBranch a1 a2) = foldr f (foldr (flip (foldr f)) z a2) a1
foldMap f (CondBranch a1 a2) = mappend (foldMap f a1) (foldMap (foldMap
f) a2)
#if MIN_VERSION_base(4,8,0)
sum = foldr (+) 0
product = foldr (*) 1
minimum = fromMaybe (error "minimum: empty") . foldr (min . Just)
Nothing
maximum = fromMaybe (error "maximum: empty") . foldr (max . Just)
Nothing
#endif
instance Foldable CondTree where
foldr f z (CondNode a) = foldr (flip (foldr f)) z a
foldMap f (CondNode a) = foldMap (foldMap f) a
#if MIN_VERSION_base(4,8,0)
sum = foldr (+) 0
product = foldr (*) 1
minimum = fromMaybe (error "minimum: empty") . foldr (min . Just)
Nothing
maximum = fromMaybe (error "maximum: empty") . foldr (max . Just)
Nothing
#endif
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13056#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list