why does the binary library require so much memory?

Hello, Using encode/decode from Binary seems to permamently increase my memory consumption by 60x fold. I am wonder if I am doing something wrong, or if this is an issue with Binary. If I run the following program, it uses sensible amounts of memory (1MB) (note that the bin and list' thunks won't actully be evaluated): import Data.Binary main :: IO () main = let list = [1..1000000] :: [Int] bin = encode list list' = decode bin :: [Int] in putStrLn (show . length $ takeWhile (< 10000000) list) >> getLine >> return () /tmp $ ghc --make -O2 Bin.hs -o bin /tmp $ ./bin +RTS -s /tmp/bin +RTS -s 1000000 68,308,156 bytes allocated in the heap 6,700 bytes copied during GC 18,032 bytes maximum residency (1 sample(s)) 22,476 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 130 collections, 0 parallel, 0.00s, 0.00s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.05s ( 0.92s elapsed) GC time 0.00s ( 0.00s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 0.05s ( 0.92s elapsed) %GC time 0.0% (0.1% elapsed) Alloc rate 1,313,542,603 bytes per MUT second Productivity 100.0% of total user, 5.7% of total elapsed According to top: VIRT RSS SHR 3880 1548 804 Now, if I change *list* in the last line to *list'* so that the encode/decode stuff actually happens: /tmp $ ./bin +RTS -s /tmp/bin +RTS -s 1000000 617,573,932 bytes allocated in the heap 262,281,412 bytes copied during GC 20,035,672 bytes maximum residency (10 sample(s)) 2,187,296 bytes maximum slop 63 MB total memory in use (0 MB lost due to fragmentation) Generation 0: 1151 collections, 0 parallel, 0.47s, 0.48s elapsed Generation 1: 10 collections, 0 parallel, 0.36s, 0.40s elapsed INIT time 0.00s ( 0.00s elapsed) MUT time 0.47s ( 20.32s elapsed) GC time 0.84s ( 0.88s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 1.30s ( 21.19s elapsed) %GC time 64.1% (4.1% elapsed) Alloc rate 1,319,520,653 bytes per MUT second Productivity 35.9% of total user, 2.2% of total elapsed And top reports: VIRT RSS SHR 67368 64m 896 63 times as much total memory in use. And, this is while the program is waiting around at 'getLine' after it is 'done' with the data. I am using GHC 6.10.4 on GNU/Linux. Thanks! - jeremy

I just need a small test case to reproduce the problem. Thanks! -- Don jeremy:
Hello,
Using encode/decode from Binary seems to permamently increase my memory consumption by 60x fold. I am wonder if I am doing something wrong, or if this is an issue with Binary.
If I run the following program, it uses sensible amounts of memory (1MB) (note that the bin and list' thunks won't actully be evaluated):
import Data.Binary
main :: IO () main = let list = [1..1000000] :: [Int] bin = encode list list' = decode bin :: [Int] in putStrLn (show . length $ takeWhile (< 10000000) list) >> getLine >> return ()
/tmp $ ghc --make -O2 Bin.hs -o bin /tmp $ ./bin +RTS -s /tmp/bin +RTS -s 1000000
68,308,156 bytes allocated in the heap 6,700 bytes copied during GC 18,032 bytes maximum residency (1 sample(s)) 22,476 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation)
Generation 0: 130 collections, 0 parallel, 0.00s, 0.00s elapsed Generation 1: 1 collections, 0 parallel, 0.00s, 0.00s elapsed
INIT time 0.00s ( 0.00s elapsed) MUT time 0.05s ( 0.92s elapsed) GC time 0.00s ( 0.00s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 0.05s ( 0.92s elapsed)
%GC time 0.0% (0.1% elapsed)
Alloc rate 1,313,542,603 bytes per MUT second
Productivity 100.0% of total user, 5.7% of total elapsed
According to top:
VIRT RSS SHR 3880 1548 804
Now, if I change *list* in the last line to *list'* so that the encode/decode stuff actually happens:
/tmp $ ./bin +RTS -s /tmp/bin +RTS -s 1000000
617,573,932 bytes allocated in the heap 262,281,412 bytes copied during GC 20,035,672 bytes maximum residency (10 sample(s)) 2,187,296 bytes maximum slop 63 MB total memory in use (0 MB lost due to fragmentation)
Generation 0: 1151 collections, 0 parallel, 0.47s, 0.48s elapsed Generation 1: 10 collections, 0 parallel, 0.36s, 0.40s elapsed
INIT time 0.00s ( 0.00s elapsed) MUT time 0.47s ( 20.32s elapsed) GC time 0.84s ( 0.88s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 1.30s ( 21.19s elapsed)
%GC time 64.1% (4.1% elapsed)
Alloc rate 1,319,520,653 bytes per MUT second
Productivity 35.9% of total user, 2.2% of total elapsed
And top reports:
VIRT RSS SHR 67368 64m 896
63 times as much total memory in use. And, this is while the program is waiting around at 'getLine' after it is 'done' with the data.
I am using GHC 6.10.4 on GNU/Linux.
Thanks! - jeremy _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Jul 31, 2009 at 1:56 PM, Jeremy Shaw
Using encode/decode from Binary seems to permamently increase my memory consumption by 60x fold. I am wonder if I am doing something wrong, or if this is an issue with Binary.
It's an issue with the Binary instance for lists, which forces the entire spine of the list too early. This gives you a gigantic structure to hold onto.

bos:
On Fri, Jul 31, 2009 at 1:56 PM, Jeremy Shaw
wrote: Using encode/decode from Binary seems to permamently increase my memory consumption by 60x fold. I am wonder if I am doing something wrong, or if this is an issue with Binary.
It's an issue with the Binary instance for lists, which forces the entire spine of the list too early. This gives you a gigantic structure to hold onto.
This is the current instance instance Binary a => Binary [a] where put l = put (length l) >> mapM_ put l get = do n <- get :: Get Int getMany n -- | 'getMany n' get 'n' elements in order, without blowing the stack. getMany :: Binary a => Int -> Get [a] getMany n = go [] n where go xs 0 = return $! reverse xs go xs i = do x <- get -- we must seq x to avoid stack overflows due to laziness in -- (>>=) x `seq` go (x:xs) (i-1) It used to be this, though, xs <- replicateM n get -- now the elems. -- Don

Hello, Is there a work-around? This is killer for Happstack. Most Happstack applications use IxSet, which in turn uses lists to serialize the data to/from disk. Also, why doesn't the stuff get freed eventually? - jeremy At Fri, 31 Jul 2009 14:27:30 -0700, Don Stewart wrote:
bos:
On Fri, Jul 31, 2009 at 1:56 PM, Jeremy Shaw
wrote: Using encode/decode from Binary seems to permamently increase my memory consumption by 60x fold. I am wonder if I am doing something wrong, or if this is an issue with Binary.
It's an issue with the Binary instance for lists, which forces the entire spine of the list too early. This gives you a gigantic structure to hold onto.
This is the current instance
instance Binary a => Binary [a] where put l = put (length l) >> mapM_ put l get = do n <- get :: Get Int getMany n
-- | 'getMany n' get 'n' elements in order, without blowing the stack. getMany :: Binary a => Int -> Get [a] getMany n = go [] n where go xs 0 = return $! reverse xs go xs i = do x <- get -- we must seq x to avoid stack overflows due to laziness in -- (>>=) x `seq` go (x:xs) (i-1)
It used to be this, though,
xs <- replicateM n get -- now the elems.
-- Don

Why don't you use your own instance to serialize IxSet lazily (or however you would like?) There's no reason to be constrained to use the [a] instance. -- Don jeremy:
Hello,
Is there a work-around? This is killer for Happstack. Most Happstack applications use IxSet, which in turn uses lists to serialize the data to/from disk.
Also, why doesn't the stuff get freed eventually?
- jeremy
At Fri, 31 Jul 2009 14:27:30 -0700, Don Stewart wrote:
bos:
On Fri, Jul 31, 2009 at 1:56 PM, Jeremy Shaw
wrote: Using encode/decode from Binary seems to permamently increase my memory consumption by 60x fold. I am wonder if I am doing something wrong, or if this is an issue with Binary.
It's an issue with the Binary instance for lists, which forces the entire spine of the list too early. This gives you a gigantic structure to hold onto.
This is the current instance
instance Binary a => Binary [a] where put l = put (length l) >> mapM_ put l get = do n <- get :: Get Int getMany n
-- | 'getMany n' get 'n' elements in order, without blowing the stack. getMany :: Binary a => Int -> Get [a] getMany n = go [] n where go xs 0 = return $! reverse xs go xs i = do x <- get -- we must seq x to avoid stack overflows due to laziness in -- (>>=) x `seq` go (x:xs) (i-1)
It used to be this, though,
xs <- replicateM n get -- now the elems.
-- Don

At Fri, 31 Jul 2009 14:49:03 -0700, Don Stewart wrote:
Why don't you use your own instance to serialize IxSet lazily (or however you would like?)
There's no reason to be constrained to use the [a] instance.
Well, the Set instance might actually be a better choice. But the Set instance in Binary uses [a] anyway :) Plus, happstack applications do also use Set and List in addition to IxSet. Is this issue with list fixable? If list can't be fixed, then perhaps Set and IxSet can't be fixed for the same reason. But, I don't really understand the reason yet. - jeremy

jeremy:
At Fri, 31 Jul 2009 14:49:03 -0700, Don Stewart wrote:
Why don't you use your own instance to serialize IxSet lazily (or however you would like?)
There's no reason to be constrained to use the [a] instance.
Well, the Set instance might actually be a better choice. But the Set instance in Binary uses [a] anyway :) Plus, happstack applications do also use Set and List in addition to IxSet.
Is this issue with list fixable? If list can't be fixed, then perhaps Set and IxSet can't be fixed for the same reason. But, I don't really understand the reason yet.
Oh, it is entirely possible to use a different instance, that has different semantics for lists. You want to write the list incrementally? -- Don

At Fri, 31 Jul 2009 15:43:49 -0700, Don Stewart wrote:
Oh, it is entirely possible to use a different instance, that has different semantics for lists. You want to write the list incrementally?
I don't think so. In happstack, the idea is to have all your state in RAM. But, since your machine sometimes goes down, etc, we also want to back it up to disk so we can restore the state after a reboot. There has also been talk recently about writing the state to /dev/null after we restore to make sure it has really been successful decoded. We don't want to lazily find out that there is undecodable data. So, the desired experience would be: 1. A program starts running and populates an IxSet. At this point in time n MB of RAM are being used. 2. We use Binary to snapshot the entire IxSet to disk. Since encode outputs an lazy ByteString, I would expect only a modest amount of additional memory to be required during this process. After the snapshot has been completed, I would expect the app to only be using around n MB of RAM. 3. the application exits and restarts 4. the application reads in the saved IxSet from disk. Afterwords it uses only around n MB of RAM. Instead, it seems like reading the state in from disk results in, n * 60, the amount of RAM being used. I am not really clear on why. It seems like the serialized version of the list is going to be *smaller* than original list, since the original list has all sorts of pointers and thunks. So, even if decode used a strict ByteString I would expect less than 2x the memory usage... Where am I going wrong here? Thanks! - jeremy

Hrm, I think actually, that my test program was a bit bogus... investigating now. - jeremy

Ok, I fixed my test program, and now things seem more reasonable. The original version was allowing the GC to collect the list in the first case, but not the second. However, I don't want the list to be collected. The new version seems to fix that issue. Now the control uses 40MB and when I change it to list' it uses 64MB. Which is more reasonable. main :: IO () main = let list = [1..1000000] :: [Int] bin = encode list list' = decode bin :: [Int] in do putStrLn (show . length $ takeWhile (< 10000000) list) getLine putStrLn (show . length $ takeWhile (< 10000001) list)

Hello Jeremy, Saturday, August 1, 2009, 3:15:02 AM, you wrote:
So, the desired experience would be:
1. A program starts running and populates an IxSet. At this point in time n MB of RAM are being used.
2. We use Binary to snapshot the entire IxSet to disk. Since encode outputs an lazy ByteString, I would expect only a modest amount of additional memory to be required during this process.
what really happens here: while you expect that intermediate list produced lazily (it's haskell, after all!) and immediately stored to disk in chunks, "length l" in Binary instance forces entire list to be calculated before producing any output it should be easy to fix: if your IxSet have builtin elements counter or way to measure it without allocating tons of memory, you just need to make something like the following instance: instance Binary a => Binary (IxSet a) where put l = put (IxSet.length l) >> mapM_ put l get = fmap list_to_IxSet get -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

2009/07/31 Jeremy Shaw
...why doesn't the stuff get freed eventually?
It is my understanding that the GHC runtime never lets go of memory once it has requested it. (Confirmation either way would be informative.) -- Jason Dusek

Hi Don, I was wondering if perhaps this might be a slightly better instance for Binary [a], that might solve a) the problem of having to traverse the entire list first, and b) the list length limitation of using length and Ints. My version is hopefully a little more lazy (taking maxBound :: Word16 elements at a time), and should potentially allow infinite lists to be stored: import Data.Binary import Data.Binary.Get import Data.Binary.Put import Data.Word newtype List a = List [a] deriving (Show,Eq) instance Binary a => Binary (List a) where put (List xs) = do let (hd,num,tl) = btake maxBound xs putWord16be num if num == 0 then return () else do mapM_ put hd put (List tl) get = do num <- getWord16be if num > 0 then do xs <- sequence (replicate (fromIntegral num) get) List ys <- get return (List (xs ++ ys)) else return (List []) btake :: Word16 -> [a] -> ([a],Word16,[a]) btake n xs = btake' n n xs btake' :: Word16 -> Word16 -> [a] -> ([a],Word16,[a]) btake' 0 m xs = ([],m,xs) btake' n m [] = ([],m-n,[]) btake' !n m (x:xs) = (x:xs',n',ys) where (xs',n',ys) = btake' (n-1) m xs My testing of this version shows that it's terribly bad when it comes to memory usage, but I'm sure someone can find a more efficient way to do what I'm trying here. -- Axman On 01/08/2009, at 07:27, Don Stewart wrote:
bos:
On Fri, Jul 31, 2009 at 1:56 PM, Jeremy Shaw
wrote: Using encode/decode from Binary seems to permamently increase my memory consumption by 60x fold. I am wonder if I am doing something wrong, or if this is an issue with Binary.
It's an issue with the Binary instance for lists, which forces the entire spine of the list too early. This gives you a gigantic structure to hold onto.
This is the current instance
instance Binary a => Binary [a] where put l = put (length l) >> mapM_ put l get = do n <- get :: Get Int getMany n
-- | 'getMany n' get 'n' elements in order, without blowing the stack. getMany :: Binary a => Int -> Get [a] getMany n = go [] n where go xs 0 = return $! reverse xs go xs i = do x <- get -- we must seq x to avoid stack overflows due to laziness in -- (>>=) x `seq` go (x:xs) (i-1)
It used to be this, though,
xs <- replicateM n get -- now the elems.
-- Don _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Alex Mason
-
Bryan O'Sullivan
-
Bulat Ziganshin
-
Don Stewart
-
Jason Dusek
-
Jeremy Shaw