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

GHC ghc-devs at haskell.org
Wed Sep 18 18:52:38 CEST 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):

 I've been able to remove all stuff from mwc-random. Here is test case.
 Again it's slow version.

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


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

 standard :: Double
 {-# INLINE standard #-}
 standard = blocks ! 0
   where
     blocks :: I.Vector Double
     blocks = I.cons r
            $ I.unfoldrN 130 go
            $ T r f
       where
         go (T b g)   = let !u = T h (exp (-0.5 * h * h))
                            h  = sqrt (-2 * log (v / b + g))
                        in Just (h, u)
     {-# NOINLINE blocks #-}

 v,r,f :: Double
 v = 9.91256303526217e-3
 r = 3.442619855899
 -- f = 2.669629083880923e-3  -- FAST
 f = exp (-0.5 * r * r)    -- SLOW

 -- Unboxed 2-tuple
 data T = T {-# UNPACK #-} !Double {-# UNPACK #-} !Double
 }}}

 Couple of observations

  1. Replacing `f` with constant restores run time to normal. AFAIR GHC
 cannot constant fold `exp` and similar functions. So it may matter

  2. Floating `block` to top level or removing `I.cons` restores run time
 too.

  3. Simplifying `go` function changes run time. Removing `sqrt` or `log`
 reduce rim time. It looks like `blocks` is reevaluated every time
 `standard` is evaluated.

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



More information about the ghc-tickets mailing list