[Haskell-beginners] space leak
Uchida Yasuo
kg6y_ucd at yahoo.co.jp
Mon Feb 15 17:42:03 EST 2010
That's right! You solved the mystery of the magic number!
--- Felipe Lessa wrote:
> You can try to verify this by using L.toChunks and noting how
> many chunks are being created.
-- test.hs
module Main where
import System
import System.IO
import qualified Data.ByteString.Lazy.Char8 as L
import qualified Data.ByteString.Char8 as S
main = do args <- getArgs
let n = read $ args !! 0
cs <- L.getContents
let !a = L.take n cs
!l = L.length a
hPutStrLn stderr $ "first chunk : "
++ show (S.length $ head $ L.toChunks cs)
mapM_ (print . L.length) $ L.lines cs
print a
$ ./gen | head -1000 | ./test 17000 +RTS -sstderr > /dev/null
./test 17000 +RTS -sstderr
first chunk : 16384
gen: <stdout>: commitAndReleaseBuffer: resource vanished (Broken pipe)
4,085,671,308 bytes allocated in the heap
7,659,656 bytes copied during GC
1,091,072 bytes maximum residency (1001 sample(s))
540,552 bytes maximum slop
5 MB total memory in use (1 MB lost due to fragmentation)
Generation 0: 6507 collections, 0 parallel, 0.10s, 0.13s elapsed
Generation 1: 1001 collections, 0 parallel, 0.09s, 0.10s elapsed
INIT time 0.00s ( 0.00s elapsed)
MUT time 2.62s ( 23.11s elapsed)
GC time 0.19s ( 0.23s elapsed)
EXIT time 0.00s ( 0.00s elapsed)
Total time 2.81s ( 23.34s elapsed)
%GC time 6.8% (1.0% elapsed)
Alloc rate 1,558,678,834 bytes per MUT second
Productivity 93.2% of total user, 11.2% of total elapsed
--
Regards,
Yasuo Uchida
More information about the Beginners
mailing list