[GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best
GHC
ghc-devs at haskell.org
Tue Sep 12 11:39:44 UTC 2017
#14208: Performance with O0 is much better than the default or with -O2, runghc
performs the best
-------------------------------------+-------------------------------------
Reporter: harendra | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by harendra):
I added a much simpler example on the "simplified" branch in the same
repo. I can paste it here as well:
Main.hs
{{{#!hs
import List
...
len :: IO Int
len = do
xs <- toList $ (foldr (<>) mempty $ map (\x -> Yield x Stop)
[1..100000 :: Int])
return (length xs)
}}}
List.hs
{{{#!hs
module List where
import Control.Monad (liftM)
data List a = Stop | Yield a (List a)
instance Monoid (List a) where
mempty = Stop
mappend x y =
case x of
Stop -> y
Yield a r -> Yield a (mappend r y)
toList :: Monad m => List a -> m [a]
toList m =
case m of
Stop -> return []
Yield a r -> liftM (a :) (toList r)
}}}
It essentially generates a custom list in the main module and calls
`toList` function from another module to covert it into a Haskell list.
The perf difference is not as dramatic as the previous example but it is
significant.
All in the same module:
{{{
-O0 : 14ms
-O1 : 8ms
-fno-pre-inlining: 4ms
}}}
Different modules:
{{{
-O0 : 8ms
-O1 : 14ms
-fno-pre-inlining: 8ms
INLINE toList : 4ms
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14208#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list