#3586: Initialisation of unboxed arrays is too slow
-----------------------------------------+----------------------------------
    Reporter:  simonpj                   |        Owner:                  
        Type:  run-time performance bug  |       Status:  new             
    Priority:  high                      |    Milestone:  6.12.2          
   Component:  libraries (other)         |      Version:  6.10.4          
    Severity:  normal                    |   Resolution:                  
    Keywords:                            |   Difficulty:  Unknown         
    Testcase:                            |           Os:  Unknown/Multiple
Architecture:  Unknown/Multiple          |  
-----------------------------------------+----------------------------------
Comment (by dons):

 Hello Philippos, you should take up these general design questions on the
 [email protected] mailing list, not on the bug tracker.

 Some quick points: since you use the mersenne-twister in Clean, you should
 use it in Haskell too: http://hackage.haskell.org/package/mersenne-random.
 Also, you should never need to increase the stack size with the -K option.
 Finally, it is faster to thread around a seed to the random generator,
 than to generate the infinite list of randoms.

 Here's how I would translate your Clean program to Haskell:

 {{{
 {-# LANGUAGE BangPatterns #-}
 {-# OPTIONS -funbox-strict-fields #-}

 --
 -- Compile with: ghc -O2 -fvia-C -optc-O3 --make A.hs
 -- Run with : ./A +RTS -H200M
 --
 -- $ time ./A +RTS -H200M
 -- 2.77000034e8
 -- ./A +RTS -H200M  0.62s user 0.10s system 96% cpu 0.751 total
 --

 import Control.Monad.ST
 import Control.Monad
 import Data.Array.ST
 import Data.Array.Base
 import System.Random.Mersenne

 data Op = And | Or | Not

 data Tree = L !Double | T !Op [Tree]

 main = do
     g  <- getStdGen
     print $ runST $ do
         let l = 0
             u = 2000000 - 1
         vt <- unsafeNewArray_ (l,u)
         forM_ [l..u] $ \i -> unsafeWrite vt i (L 137)
         fn u vt 0 g

 fn :: Int -> STArray s Int Tree -> Double -> MTGen -> ST s Double
 fn i a !acc g | i < 1     = return acc
 fn i a  acc g = do
     i1 <- ri `fmap` unsafeIOToST (random g) :: ST s Int
     i2 <- ri `fmap` unsafeIOToST (random g) :: ST s Int
     b <- a `readArray` i1
     writeArray a i2 (set (get b + 3))
     c <- a `readArray` i1
     fn (i-1) a (get c + acc) g

 ri :: Int -> Int
 ri x = (abs x) `rem` 2000000

 get :: Tree -> Double
 get (L r) = r
 get _     = 0.0

 set :: Double -> Tree
 set r = L r
 }}}

 Your Haskell version completes for me in just over 2 minutes. The above
 Haskell version completes in 0.7s. I'd imagine this is very competitive
 with the Clean implementation? I give detailed instructions on how to
 compile this for best results.

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