#3586: Slow array code
-----------------------------------------+----------------------------------
    Reporter:  simonpj                   |        Owner:                  
        Type:  run-time performance bug  |       Status:  new             
    Priority:  normal                    |    Milestone:                  
   Component:  Compiler                  |      Version:  6.10.4          
    Severity:  normal                    |   Resolution:                  
    Keywords:                            |   Difficulty:  Unknown         
    Testcase:                            |           Os:  Unknown/Multiple
Architecture:  Unknown/Multiple          |  
-----------------------------------------+----------------------------------
Comment (by dons):

 Isn't the problem here that you're using unboxed arrays in Clean, but
 boxed arrays in Haskell?

 Secondly, there's a space leak in the fn function, and a bunch of things
 that aren't in the Clean code. Fixing things:

 Correcting the space leak:
 {{{
 {-# LANGUAGE BangPatterns #-}

 import Control.Monad.ST
 import Data.Array.ST
 main = print $ runST
           (do arr <- newArray (1,2000000)
                         137.0 :: ST s
                                   (STArray s
                                     Int Double)
               a <- readArray arr 1
               b <- readArray arr 1
               fn 2000000 arr 0.0 )


 fn i !a !acc | i < 1 = do (return acc)
 fn i a acc= do
              b <- readArray a i
              writeArray a i (b+3.0)
              c <- readArray a i
              fn (i-1) a (acc+c)
 }}}

 Results in:

 {{{
 $ time ./B +RTS -sstderr
 ./B +RTS -sstderr
 2.8e8

 ./B +RTS -sstderr  2.95s user 0.07s system 99% cpu 3.034 total
 }}}

 3.034s

 Where 98.6% of the time is spent in GC (this is why you don't use boxed
 mutable arrays when you can use unboxed ones.

 Increasing the GC thresholds, improves performance 20 fold:
 {{{
 $ time ./B +RTS -sstderr -A200M
 ./B +RTS -sstderr -A200M
 2.8e8

 ./B +RTS -sstderr -A200M  0.06s user 0.12s system 100% cpu 0.176 total
 }}}

 0.176s using boxed arrays. Switching to an STUArray, and adding some type
 annotations:

 {{{
 {-# LANGUAGE BangPatterns #-}
 {-# OPTIONS -fexcess-precision #-}

 import Control.Monad.ST
 import Data.Array.ST
 import Data.Array.Base

 main = print $ runST
           (do arr <- newArray (1,2000000) 137.0 :: ST s (STUArray s Int
 Double)
               fn 2000000 arr 0.0 )


 fn :: Int -> STUArray s Int Double -> Double -> ST s Double
 fn i !a !acc | i < 1 = return acc
 fn i a acc = do
      b <- unsafeRead a i
      unsafeWrite a i (b+3.0)
      c <- unsafeRead a i
      fn (i-1) a (c + acc)


 ./B +RTS -sstderr  0.26s user 0.01s system 97% cpu 0.283 total
 }}}

 So still not great. Perhaps someone can look into it further?

 The original bug report is a duplicate of the boxed, mutable arrays
 ticket.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3586#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to