
What does ordinary heap profiling (-hc, -hd, -hy) tell you about what's in the heap? These options should work fine with STM. Cheers, Simon On 16 December 2005 11:44, Joel Reymont wrote:
Folks,
I have a huge space leak someplace and I suspect this code. The SrvServerInfo data structure is something like 50K compressed or uncompressed byte data before unpickling. My thousands of bots issue this request at least once and I almost run out of memory with 100 bots on a 1Gb machine on FreeBSD. Do I need deepSeq somewhere below?
This is the read.
read :: Handle -> (SSL, BIO, BIO) -> IO Command read h _ = do sa <- emptyByteArray 4 hGetArray h sa 4 (size', _) <- unpickle endian32 sa 0 let size = fromIntegral $ size' - 4 packet <- emptyByteArray size hGetArray h packet size unstuff packet 0
I suspect that I need to deepSeq cmd'' instead of return $! cmd''
unstuff :: MutByteArray -> Index -> IO Command unstuff array ix = do (kind, ix1) <- unpickle puCmdType array ix (cmd', _) <- unpickle (puCommand kind) array ix1 case cmd' of InvalidCommand -> do fail $ "unstuff: Cannot parse " ++ show array SrvCompressedCommands sz bytes -> do bytes' <- uncompress bytes (fromIntegral sz) cmd'' <- unstuff bytes' 4 return $! cmd'' _ -> return cmd'
This is where the list of active tables is converted to a table id list of [Word32].
pickTable _ filters (Cmd cmd@(SrvServerInfo {})) = do let tables = filter (tableMatches filters) $ activeTables cmd ids = map tiTableID tables case tables of [] -> fail $ "pickTable: No tables found: " ++ show filters _ -> do pop stoptimer "pickTable" return $! Eat $! Just $! Custom $! Tables $! ids
This is where the table id list of [Word32] is consumed.
takeEmptySeat _ aff_id _ (Custom (Tables ids@(table:rest))) = do trace 85 $ "takeEmptySeat: " ++ show (length ids) ++ " tables found" trace 100 $ "takeEmptySeat: tables: " ++ showTables ids trace 85 $ "takeEmptySeat: trying table# " ++ show table w <- get put_ $ w { tables_to_try = rest } push "goToTable" $ goToTable table aff_id -- kick off goToTable return $ Eat $ Just Go
This is the SrvServerInfo structure.
| SrvServerInfo { activeTables :: ![TableInfo], -- Word16/ removedTables :: ![Word32], -- Word16/ version :: !Int32 }
And this is the table info itself.
data TableInfo = TableInfo { tiAvgPot :: !Word64, tiNumPlayers :: !Word16, tiWaiting :: !Word16, tiPlayersFlop :: !Word8, tiTableName :: !String, tiTableID :: !Word32, tiGameType :: !GameType, tiInfoMaxPlayers :: !Word16, tiIsRealMoneyTable :: !Bool, tiLowBet :: !Word64, tiHighBet :: !Word64, tiMinStartMoney :: !Word64, tiMaxStartMoney :: !Word64, tiGamesPerHour :: !Word16, tiTourType :: !TourType, tiTourID :: !Word32, tiBetType :: !BetType, tiCantReturnLess :: !Word32, tiAffiliateID :: ![Word8], tiLangID :: !Word32 } deriving (Show, Typeable)
Thanks, Joel

-hc points to script#9 below. script (_, _, affid) (Custom (JoinedTable 0)) = do {-# SCC "script#8" #-}push "takeEmptySeat" $ {-# SCC "script#9" #-}takeEmptySeat Holdem affid [] {-# SCC "script#10" #-}return $ Eat $ Just Go What takeEmptySeat does it call pickTable takeEmptySeat game_type _ filters Go = do push "pickTable" $ pickTable game_type filters return $ Eat $ Just Go pickTable retrieves the list of SrvServerInfo structures, etc. Overall, -hc does not help me figure out where my data is being retained. My understanding is that I need to do -hbdrag,void fo rthat. I did not try -hd and -hy, they would only help me narrow down the producers, right? My program seems to spend 70% of the time collecting garbage. Notice the HUGE overall allocations. This is my trying to launch 4k bots over 8 hours. Only 1k bots were launched and just 300 of those got to play. Maybe because they did not have time with all the garbage collection :-). The tests that I ran previously did not involve heavy network traffic, just a few very small packets. This is why I was able to get to thousands of bots in just a couple of hours and keep them there. ./randomplay +RTS -k3k -P -hc -srandomplay.gc 95,739,560,464 bytes allocated in the heap 887,633,330,904 bytes copied during GC 131,849,008 bytes maximum residency (8730 sample(s)) 330325 collections in generation 0 (557.40s) 8730 collections in generation 1 (16370.05s) 248 Mb total memory in use INIT time 0.00s ( 0.03s elapsed) MUT time 783.40s (1872.75s elapsed) GC time 16927.45s (20075.68s elapsed) RP time 0.00s ( 0.00s elapsed) PROF time 6003.62s (7058.40s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 23714.47s (29006.86s elapsed) %GC time 71.4% (69.2% elapsed) <---- isn't this aweful? Alloc rate 122,210,314 bytes per MUT second Productivity 3.3% of total user, 2.7% of total elapsed On Dec 16, 2005, at 11:53 AM, Simon Marlow wrote:
What does ordinary heap profiling (-hc, -hd, -hy) tell you about what's in the heap? These options should work fine with STM.

I uploaded the full reports to http://wagerlabs.com/randomplay.tgz On Dec 16, 2005, at 11:53 AM, Simon Marlow wrote:
What does ordinary heap profiling (-hc, -hd, -hy) tell you about what's in the heap? These options should work fine with STM.
participants (2)
-
Joel Reymont
-
Simon Marlow