RE: [Haskell-cafe] Battling laziness

On 16 December 2005 12:42, Joel Reymont wrote:
On Dec 16, 2005, at 12:36 PM, Simon Marlow wrote:
If script#9 is the cost center attached to all of your leaking heap data, then you're already a long way to finding the problem. It'll help even more to find out whether it is just unevaluated copies of "takeEmptySeat Holdem affid []", or something else (-hd, -hy will help here). Try +RTS -hy -hcscript#9, for example.
One obvious thing to try is replacing the '$' before {-# SCC "script#9" #-} with '$!'. And similarly in takeEmptySeat.
Let me try these and report my findings.
(I should say that we definitely plan to update these for STM, but it's not completely trivial (I checked). Volunteers definitely welcome).
I volunteer! Just need some pointers on where to get started. I learn quickly but need to be guided ;-). Plus, I need this the most, right?
I was slightly mistaken: lag/drag/void profiling is pretty easy. Take a look at ghc/rts/LdvProfile.c and add relevant cases for STM objects to processHeapClosureForDead(). If you fix this up and test it we should be able to get it into 6.4.2. Retainer profiling is much harder; the code is in RetainerProfile.c/RetainerSet.c. Cheers, Simon

The result of ./randomplay +RTS -p -hd -hclaunchScripts#8 is at http://wagerlabs.com/randomplay.hd.ps Thanks, Joel -- http://wagerlabs.com/

Looking at http://wagerlabs.com/randomplay.hd.ps I see closures
(constructors?) in this order
IO () copyMArray _ _ _ _ 0 = return () copyMArray dest ix src src_ix n = do e <- readArray src src_ix writeArray dest ix e copyMArray dest (ix + 1) src (src_ix + 1) (n - 1)
copyIArray :: MutByteArray -> Index -> ByteArray -> Index -> Int -> IO () copyIArray _ _ _ _ 0 = return () copyIArray dest ix src src_ix n = do let e = src ! src_ix writeArray dest ix e copyIArray dest (ix + 1) src (src_ix + 1) (n - 1) readBits :: forall a.(Num a, Bits a) => MutByteArray -> Index -> IO a readBits array ix = readBits' array ix bitsize 0 where bitsize = bitSize (undefined :: a) readBits' _ _ 0 acc = return acc readBits' array ix count acc = do e <- readArray array ix let e' = (fromIntegral e) `shiftL` (count - 8) readBits' array (ix + 1) (count - 8) (acc + e') writeBits :: (Integral a, Bits a) => MutByteArray -> Index -> a -> IO () writeBits array ix a = writeBits' array ix (bitSize a) where writeBits' _ _ 0 = return () writeBits' array ix count = do let mask = 0xff `shiftL` (count - 8) a' = (a .&. mask) `shiftR` (count - 8) a'' = fromIntegral a' writeArray array ix a'' writeBits' array (ix + 1) (count - 8) withByteArray :: ByteArray -> (Ptr Word8 -> IO a) -> IO a withByteArray array fun = do let size = arraySize array allocaBytes size $ \ptr -> do copyBytes ptr array 0 size fun ptr where copyBytes _ _ _ 0 = return () copyBytes ptr arr ix sz = do poke ptr (arr ! ix) copyBytes (advancePtr ptr 1) arr (ix + 1) (sz - 1) byteArrayFromPtr :: Ptr Word8 -> Int -> IO MutByteArray byteArrayFromPtr ptr sz = do array <- emptyByteArray sz copyBytes array ptr 0 sz return array where copyBytes _ _ _ 0 = return () copyBytes array ptr ix n = do e <- peek ptr writeArray array ix e copyBytes array (advancePtr ptr 1) (ix + 1) (n - 1) instance Show MutByteArray where show a = show $ unsafePerformIO $ getElems a
participants (2)
-
Joel Reymont
-
Simon Marlow