[GHC] #10400: Run time increases by 40% in fractal plotter core loop

GHC ghc-devs at haskell.org
Sun May 10 18:02:00 UTC 2015


#10400: Run time increases by 40% in fractal plotter core loop
-------------------------------------+-------------------------------------
              Reporter:  saffroy     |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.8.4
              Keywords:              |  Operating System:  Linux
          Architecture:  x86_64      |   Type of failure:  Runtime
  (amd64)                            |  performance bug
             Test Case:              |        Blocked By:
              Blocking:              |   Related Tickets:
Differential Revisions:              |
-------------------------------------+-------------------------------------
 I'm writing a toy fractal plotter to teach myself some Haskell. For a
 while I used GHC 7.4, recently upgraded to 7.10, and found a significant
 drop in run time performance. Tests with other versions show that the drop
 dates back to 7.8.

 Not sure if this is a good practice, or if this is relevant here, but I
 used bangs to improve performance by adding strictness: this gives a good
 speedup with 7.4/7.6, but perf is unchanged with 7.8/7.10.

 || version || run time (sec) - bangs || no bangs ||
 ||7.4.2 || 6.09|| 18.73||
 ||7.6.3 || 6.10|| 18.93||
 ||7.8.4 || 8.92|| 8.88||
 ||7.10.1 || 8.92|| 9.04||

 (All builds with ghc -O2.)

 Source:
 {{{#!hs
 {-# LANGUAGE BangPatterns #-}

 iterations :: Int -> Double -> Double -> Double -> Double -> Int -> Int
 iterations !maxK !x !y !x0 !y0 !k =
   let !x2 = x * x
       !y2 = y * y
   in
    if k == maxK || x2 + y2 > 4
    then k
    else iterations maxK (x2 - y2 + x0) (2 * x * y + y0) x0 y0 (k + 1)

 inSet :: Int -> Int -> (Double, Double) -> Bool
 inSet !minK !maxK (!x, !y) = k >= minK && k < maxK
   where !k = iterations maxK x y x y 0

 main = do
     let pointSource = repeat $ ((-0.6518209274278592), 0.3549264214581329)
         nPoints =  1000 * 1000
         points = take nPoints pointSource
         selected = filter (inSet 1000 (1000 * 20)) points
     print $ length selected == nPoints
 }}}

 The host C compiler is gcc 4.7.2.

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


More information about the ghc-tickets mailing list