[Haskell-cafe] Memory usage when passing arrays in state
Daniel Peebles
pumpkingod at gmail.com
Tue Mar 3 20:15:28 EST 2009
This may be completely unrelated to your problem, but there's a ticket
in the GHC trac saying that DiffArray is unusably slow:
http://hackage.haskell.org/trac/ghc/ticket/2727 . It doesn't analyze
the cause of the slowness, so it's quite possible that it may be
related to GC as in your case.
Cheers,
Dan
On Tue, Mar 3, 2009 at 7:44 PM, Tobias Olausson <tobsan at gmail.com> wrote:
> Hello all.
> I am currently implementing an emulation of a CPU, in which the CPU's
> RAM is part of the internal state
> that is passed around in the program using a state monad. However, the
> program performs
> unexpectingly bad, and some profiling information makes us believe
> that the problem is the high
> memory usage of the program.
>
> The program below is similar to our main program used when testing a
> sorting algorithm in this CPU:
>
> module Main where
>
> import Control.Monad.State.Lazy
> import Data.Word
> import Data.Array.Diff
> import Control.Concurrent (threadDelay)
>
> data LoopState = LoopState
> { intVal :: Integer
> , diff :: DiffUArray Word8 Word8
> }
>
> initState :: LoopState
> initState = LoopState 0 (array (0x00,0xFF) [(idx,0)|idx<-[0x00..0xFF]])
>
> main :: IO ()
> main = do
> execStateT looper initState >>= putStrLn . show . intVal
>
> looper :: StateT LoopState IO ()
> looper = do
> st <- get
> let res = intVal st + 1
> idx = fromIntegral res
> put $ st { intVal = res, diff = (diff st) // [(idx,idx)] }
> if res == 13000000
> then return ()
> else looper
>
> Of course our program does more than updating a counter ;-)
> Compiling and running this program yields the following result:
>
> [~]:[olaussot] >> ghc --make -O2 -o array ArrayPlay.hs
> [~]:[olaussot] >> ./array +RTS -sstderr
> ./array +RTS -sstderr
> 13000000
> 313,219,740 bytes allocated in the heap
> 1,009,986,984 bytes copied during GC
> 200,014,828 bytes maximum residency (8 sample(s))
> 4,946,648 bytes maximum slop
> 393 MB total memory in use (3 MB lost due to fragmentation)
>
> Generation 0: 590 collections, 0 parallel, 3.06s, 3.09s elapsed
> Generation 1: 8 collections, 0 parallel, 3.56s, 4.21s elapsed
>
> INIT time 0.00s ( 0.00s elapsed)
> MUT time 0.27s ( 0.27s elapsed)
> GC time 6.62s ( 7.30s elapsed)
> EXIT time 0.00s ( 0.00s elapsed)
> Total time 6.89s ( 7.57s elapsed)
>
> %GC time 96.1% (96.4% elapsed)
>
> Alloc rate 1,155,958,754 bytes per MUT second
>
> Productivity 3.9% of total user, 3.6% of total elapsed
>
> Why does the program spend 96.1% of its total running time collecting garbage?
> Any tips to make this program perform better are appreciated.
> Please do tell if anything is unclear.
>
> --
> Tobias Olausson
> tobsan at gmail.com
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list