memory slop
Simon Marlow
marlowsd at gmail.com
Thu Apr 14 10:24:06 CEST 2011
On 23/03/2011 02:32, Tim Docker wrote:
> The code is below. I'm mostly concerned with the memory usage rather
> than performance at this stage. What is interesting, is that when I turn
> on garbage collection statistics (+RTS -s), I see this:
>
> 10,089,324,996 bytes allocated in the heap
> 201,018,116 bytes copied during GC
> 12,153,592 bytes maximum residency (8 sample(s))
> 59,325,408 bytes maximum slop
> 114 MB total memory in use (1 MB lost due to fragmentation)
>
> Generation 0: 19226 collections, 0 parallel, 1.59s, 1.64selapsed
> Generation 1: 8 collections, 0 parallel, 0.04s, 0.04selapsed
>
> INIT time 0.00s ( 0.00s elapsed)
> MUT time 5.84s ( 5.96s elapsed)
> GC time 1.63s ( 1.68s elapsed)
> EXIT time 0.00s ( 0.00s elapsed)
> Total time 7.47s ( 7.64s elapsed)
>
> %GC time 21.8% (22.0% elapsed)
>
> Alloc rate 1,726,702,840 bytes per MUT second
>
> Productivity 78.2% of total user, 76.5% of total elapsed
>
> This seems strange. The maximum residency of 12MB sounds about correct
> for my data. But what's with the 59MB of "slop"?
I made some changes to the storage manager in the runtime today, and
fixed the slop problem with your program. Here it is after the changes:
14,928,031,040 bytes allocated in the heap
313,542,200 bytes copied during GC
18,044,096 bytes maximum residency (7 sample(s))
294,256 bytes maximum slop
37 MB total memory in use (0 MB lost due to fragmentation)
INIT time 0.00s ( 0.00s elapsed)
MUT time 6.38s ( 6.39s elapsed)
GC time 1.26s ( 1.26s elapsed)
EXIT time 0.00s ( 0.00s elapsed)
Total time 7.64s ( 7.64s elapsed)
I think this is with a different workload than the one you used above.
Before the change I was getting
15,652,646,680 bytes allocated in the heap
312,402,760 bytes copied during GC
17,913,816 bytes maximum residency (9 sample(s))
111,424,792 bytes maximum slop
142 MB total memory in use (0 MB lost due to fragmentation)
INIT time 0.00s ( 0.00s elapsed)
MUT time 8.01s ( 8.02s elapsed)
GC time 16.86s ( 16.89s elapsed)
EXIT time 0.00s ( 0.00s elapsed)
Total time 24.88s ( 24.91s elapsed)
(GHC 7.0.3 on x86-64/Linux) So, a pretty dramatic improvement. I'm
validating the patch right now, it should be in 7.2.1.
Cheers,
Simon
>
> -------- Map2.hs --------------------------------------------
>
> module Main where
>
> import qualified Data.Map as Map
> import qualified Data.ByteString.Char8 as BS
> import System.Environment
> import System.IO
>
> type MyMap = Map.Map BS.ByteString BS.ByteString
>
> foldLines :: (a -> String -> a) -> a -> Handle -> IO a
> foldLines f a h = do
> eof <- hIsEOF h
> if eof
> then (return a)
> else do
> l <- hGetLine h
> let a' = f a l
> a' `seq` foldLines f a' h
>
> undumpFile :: FilePath -> IO MyMap
> undumpFile path = do
> h <- openFile path ReadMode
> m <- foldLines addv Map.empty h
> hClose h
> return m
> where
> addv m "" = m
> addv m s = let (k,v) = readKV s
> in k `seq` v `seq` Map.insert k v m
>
> readKV s = let (ks,vs) = read s in (BS.pack ks, BS.pack vs)
>
> dump :: [(BS.ByteString,BS.ByteString)] -> IO ()
> dump vs = mapM_ putV vs
> where
> putV (k,v) = putStrLn (show (BS.unpack k, BS.unpack v))
>
> main :: IO ()
> main = do
> args <- getArgs
> case args of
> [path] -> do
> v <- undumpFile path
> dump (Map.toList v)
> return ()
>
>
>
>
>
>
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list