#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):
How I'd write it:
{{{
{-# 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 arr <- newArray (1,2000000) 137.0 :: ST s (STUArray s Int
Double)
go arr 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)
}}}
Which yield this loop for 'go':
{{{
Main_zdwa_info:
leaq 16(%r12), %rax
cmpq %r15, %rax
movq %rax, %r12
ja .L4
testq %rdi, %rdi
jle .L5
leaq 16(%rsi,%rdi,8), %rdx
leaq -16(%rax), %r12
leaq -1(%rdi), %rdi
movsd (%rdx), %xmm0
addsd .LC0(%rip), %xmm0
addsd %xmm0, %xmm5
movsd %xmm0, (%rdx)
jmp Main_zdwa_info
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3586#comment:2>
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