#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):

 The problem in the STUArray version is newArray_, which uses the generic
 newArray, which fills from a list. It does not fuse.

 Rewriting the STUArray version to initialize directly and we get identical
 results to Clean.

 {{{
 {-# LANGUAGE BangPatterns #-}
 {-# OPTIONS -fvia-C -optc-O3 -fexcess-precision -optc-msse3 #-}

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

 main = print $ runST
           (do a <- unsafeNewArray_ (1,2000000)

               let init i | i >= 2000000 = return ()
                          | otherwise    = unsafeWrite a i 137 >> init
 (i+1)
               init 0

               go a 2000000 0.0 )


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

 $ ghc -O2 --make B.hs -fvia-C -optc-O3 -optc-msse4
 [1 of 1] Compiling Main             ( B.hs, B.o )
 Linking B ...

 $ time ./B
 2.79999863e8
 ./B  0.01s user 0.02s system 108% cpu 0.031 total
 }}}

 Recommendation: custom newArray_ methods in the Data.Array.Base module
 that fill directly with a tail recursive loop.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3586#comment:5>
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