[GHC] #6166: Performance regression in mwc-random since 7.0.x

GHC ghc-devs
Tue Oct 1 18:34:10 UTC 2013


#6166: Performance regression in mwc-random since 7.0.x
--------------------------------------------+------------------------------
        Reporter:  bos                      |            Owner:
            Type:  bug                      |           Status:  new
        Priority:  high                     |        Milestone:  7.6.2
       Component:  Compiler                 |          Version:  7.4.2
      Resolution:                           |         Keywords:
Operating System:  Unknown/Multiple         |     Architecture:  x86_64
 Type of failure:  Runtime performance bug  |  (amd64)
       Test Case:                           |       Difficulty:  Unknown
        Blocking:                           |       Blocked By:
                                            |  Related Tickets:
--------------------------------------------+------------------------------

Comment (by Khudyakov):

 Another simplification

 {{{
 {-# LANGUAGE BangPatterns #-}
 import qualified Data.Vector.Unboxed as I
 import           Data.Vector.Unboxed   ((!))
 import Control.Monad

 main :: IO ()
 main = replicateM_ (200*1000) (return $! standard)

 standard :: Double
 -- Removing or replacing with NOINLINE returns perfomance to normal
 {-# INLINE standard #-}
 standard = blocks ! 0
   where
     blocks :: I.Vector Double
     blocks = I.cons 0.123
            $ I.unfoldrN 130 go (T f)
       where
         go q@(T a) = Just (log (exp a), q)
     {-# NOINLINE blocks #-}

 r,f :: Double
 r = 3.442619855899
 -- replacing f with constant return perfomance to normal
 -- f = 2.669629083880923e-3
 f = exp (-0.5 * r * r)

 -- replacing data with newtype returns performance to normal
 data T = T {-# UNPACK #-} !Double
 }}}

 Problem is visible at the core level. Code is compiled down to the
 something similar to following pseudocode:

 {{{
 loop i = if i /= 0
          then evaluate (blocks ! 0) >> loop (i-1)
          else return ()
 }}}

 blocks array is inlied despite being marked as NOINLINE and is evaluated
 on each iteration so performance is abysmal. When small chages to the
 program are made it's not inlined and evaluated only once.

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



More information about the ghc-tickets mailing list